Re: [Haskell-cafe] Help me understand general recursion from cata- and anamorphism

2013-06-23 Thread Takayuki Muranushi
Dear all, https://github.com/nushio3/practice/blob/master/recursion-schemes/FibTest.hs After learning fix-point operators, I found an answer by myself. ``` fibBase :: (Integer - Integer) - Integer - Integer fibBase fib n | n = 1= 1 | otherwise = fib (n-1) + fib (n-2) fibWithFix

[Haskell-cafe] Help me understand general recursion from cata- and anamorphism

2013-06-16 Thread Takayuki Muranushi
In an attempt to understand why cata- and anamorphisms are considered so important, I found multiple implications that you can write any recursive functions in terms of nonrecursive functions and ana, cata (am I right here?) so I'm trying to practice the rewrite by a few functions. I'm following a

Re: [Haskell-cafe] Parser left recursion

2013-03-02 Thread Roman Cheplyaka
library which is suitable for mid-scale NLP work, so handles left recursion and (high amounts of) ambiguity to produce a packed result (which can be decoded to a list of results if required). It uses a technique similar to Danielsson's for termination. The technical details (incl papers) can

Re: [Haskell-cafe] Parser left recursion

2013-02-28 Thread Paul Callaghan
Hi Another alternative is this Haskell library: https://github.com/paulcc/xsaiga This is a combinator library which is suitable for mid-scale NLP work, so handles left recursion and (high amounts of) ambiguity to produce a packed result (which can be decoded to a list of results if required

Re: [Haskell-cafe] Parser left recursion

2013-02-26 Thread Martin Drautzburg
On Sunday, 24. February 2013 16:04:11 Tillmann Rendel wrote: Both approaches are essentially equivalent, of course: Before considering the very same nonterminal again, we should have consumed at least one token. I see. Thanks So for the laymen: expr ::= expr + expr is a problem, because

Re: [Haskell-cafe] Parser left recursion

2013-02-26 Thread Dominique Devriese
2013/2/26 Martin Drautzburg martin.drautzb...@web.de: I wonder if I can enforce the nonNr property somehow, i.e. enforce the rule will not consider the same nonterminal again without having consumed any input. You might be interested in this paper: Danielsson, Nils Anders. Total parser

Re: [Haskell-cafe] Parser left recursion

2013-02-24 Thread Martin Drautzburg
On Wednesday, 20. February 2013 09:59:47 Tillmann Rendel wrote: So the grammar is: Exp ::= Int | Exp + Exp My naive parser enters an infinite recursion, when I try to parse 1+2. I do understand why: hmm, this expression could be a plus, but then it must start

Re: [Haskell-cafe] Parser left recursion

2013-02-24 Thread Tillmann Rendel
Hi Martin, Martin Drautzburg wrote: Note that the left recursion is already visible in the grammar above, no need to convert to parser combinators. The problem is that the nonterminal Exp occurs at the left of a rule for itself. Just a silly quick question: why isn't right-recursion a similar

Re: [Haskell-cafe] Parser left recursion

2013-02-24 Thread Roman Cheplyaka
* Martin Drautzburg martin.drautzb...@web.de [2013-02-24 12:31:37+0100] Twan van Laarhoven told me that: Left-recursion is always a problem for recursive-descend parsers. Note that the left recursion is already visible in the grammar above, no need to convert to parser combinators

Re: [Haskell-cafe] Parser left recursion

2013-02-24 Thread Kim-Ee Yeoh
On Sun, Feb 24, 2013 at 7:09 PM, Roman Cheplyaka r...@ro-che.info wrote: Thus, your recursion is well-founded — you enter the recursion with the input strictly smaller than you had in the beginning. Perhaps you meant /productive/ corecursion? Because the definition A ::= B A you gave

Re: [Haskell-cafe] Parser left recursion

2013-02-24 Thread Roman Cheplyaka
* Kim-Ee Yeoh k...@atamo.com [2013-02-24 19:22:33+0700] On Sun, Feb 24, 2013 at 7:09 PM, Roman Cheplyaka r...@ro-che.info wrote: Thus, your recursion is well-founded — you enter the recursion with the input strictly smaller than you had in the beginning. Perhaps you meant /productive

Re: [Haskell-cafe] Parser left recursion

2013-02-24 Thread Roman Cheplyaka
* Kim-Ee Yeoh k...@atamo.com [2013-02-24 19:22:33+0700] On Sun, Feb 24, 2013 at 7:09 PM, Roman Cheplyaka r...@ro-che.info wrote: Thus, your recursion is well-founded — you enter the recursion with the input strictly smaller than you had in the beginning. Perhaps you meant /productive

Re: [Haskell-cafe] Parser left recursion

2013-02-24 Thread Kim-Ee Yeoh
. I don't see any of this. That's when I remembered that well-founded recursion (a desirable) is sometimes confused with productive corecursion (another desirable). -- Kim-Ee ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org

Re: [Haskell-cafe] Parser left recursion

2013-02-24 Thread Roman Cheplyaka
functions) which parse a left-recursive and a non-left-recursive grammars, and see in which case the recursion is well-founded and why. Roman ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Parser left recursion

2013-02-24 Thread Kim-Ee Yeoh
On Sun, Feb 24, 2013 at 8:03 PM, Roman Cheplyaka r...@ro-che.info wrote: It may become more obvious if you try to write two recursive descent parsers (as recursive functions) which parse a left-recursive and a non-left-recursive grammars, and see in which case the recursion is well-founded

Re: [Haskell-cafe] Parser left recursion

2013-02-24 Thread Brandon Allbery
On Sun, Feb 24, 2013 at 6:31 AM, Martin Drautzburg martin.drautzb...@web.de wrote: Just a silly quick question: why isn't right-recursion a similar problem? Very roughly: Left recursion is: let foo n = n + foo n in ... Right recursion is: let foo 1 = 1; foo n = n + foo (n - 1

Re: [Haskell-cafe] Parser left recursion

2013-02-24 Thread Tillmann Rendel
(drop n1 text) of Nothing - Nothing Just n2 - Just (n1 + n2) Note that parseA is recursive. The recursion is well-founded if (drop n1 text) is smaller then text. So we have two cases, as Roman wrote: If the language defined by B contains the empty string, then n1 can be 0, so

Re: [Haskell-cafe] Parser left recursion

2013-02-24 Thread Kim-Ee Yeoh
On Sun, Feb 24, 2013 at 10:04 PM, Tillmann Rendel ren...@informatik.uni-marburg.de wrote: The recursion is well-founded if (drop n1 text) is smaller then text. So we have two cases, as Roman wrote: If the language defined by B contains the empty string, then n1 can be 0, so the recursion

Re: [Haskell-cafe] Parser left recursion

2013-02-24 Thread wren ng thornton
the inductive hypothesis vs when to bottom out at a base case. Using this grammar as-is, the recursive descent parser always decides to use the inductive hypothesis. Hence, infinite loop. It should be apparent that this isn't an issue with left-recursion (when reading the string from right to left), because

Re: [Haskell-cafe] Parser left recursion

2013-02-21 Thread S. Doaitse Swierstra
and Erik Meijer}, volume = {925}, series = {Lecture Notes in Computer Science}, publisher = {Springer}, isbn = {3-540-59451-5}, } Most left recursion stems from the fact that conventional CFG notation is sufficient, but unfortunately not ideally suited, to express oft occurring patterns

Re: [Haskell-cafe] Parser left recursion

2013-02-20 Thread Dmitry Olshansky
answered. As an exercise I am writing a parser roughly following the expamples in Graham Hutton's book. The language contains things like: data Exp = Lit Int -- literal integer | Plus Exp Exp My naive parser enters an infinite recursion, when I try to parse 1+2. I do understand why

Re: [Haskell-cafe] Parser left recursion

2013-02-20 Thread Tillmann Rendel
enters an infinite recursion, when I try to parse 1+2. I do understand why: hmm, this expression could be a plus, but then it must start with an expression, lets check. and it tries to parse expression again and again considers Plus. Indeed. Twan van Laarhoven told me that: Left-recursion

Re: [Haskell-cafe] Parser left recursion

2013-02-20 Thread Roman Cheplyaka
* Tillmann Rendel ren...@informatik.uni-marburg.de [2013-02-20 09:59:47+0100] One way to fix this problem is to refactor the grammar in order to avoid left recursion. So let's distinguish expressions that can start with expressions and expressions that cannot start with expressions

Re: [Haskell-cafe] Parser left recursion

2013-02-20 Thread Tillmann Rendel
Hi, Roman Cheplyaka wrote: Another workaround is to use memoization of some sort — see e.g. GLL (Generalized LL) parsing. Is there a GLL parser combinator library for Haskell? I know about the gll-combinators for Scala, but havn't seen anything for Haskell. Bonus points for providing the

Re: [Haskell-cafe] Parser left recursion

2013-02-20 Thread Roman Cheplyaka
* Tillmann Rendel ren...@informatik.uni-marburg.de [2013-02-20 12:39:35+0100] Hi, Roman Cheplyaka wrote: Another workaround is to use memoization of some sort — see e.g. GLL (Generalized LL) parsing. Is there a GLL parser combinator library for Haskell? I know about the gll-combinators

Re: [Haskell-cafe] Parser left recursion

2013-02-20 Thread Dominique Devriese
All, Many (but not all) of the parsing algorithms that support left recursion cannot be implemented in Haskell using the standard representation of recursion in parser combinators. The problem can be avoided in Scala because it has imperative features like referential identity and/or mutable

Re: [Haskell-cafe] Parser left recursion

2013-02-20 Thread Stephen Tetley
More primitively, Parsec and its predecessor Hutton-Meijer provide the chainl/chainr combinators, these automatically remove left recursion within the parser - i.e. you don't have to rewrite the grammar. On 20 February 2013 08:19, Dmitry Olshansky olshansk...@gmail.com wrote: Did you see

Re: [Haskell-cafe] Parser left recursion

2013-02-20 Thread Martin Drautzburg
Thank you very much. To clarify: I am not in need of a parser, I just wanted to understand why left recursion is an issue (that was easy) and what techniques help to circumvent the problem. So your answer was spot-on (though I haven't implemented it yet) On Wednesday, 20. February 2013 09:59

Re: [Haskell-cafe] adding recursion to a DSL

2013-02-19 Thread Emil Axelsson
You probably don't need recursion in the DSL for this (that would require a way to detect cycles in the expressions). For this example, it looks like all you need is to add something like `map` as a DSL construct. Your example could perhaps be expressed as forEach (1,1000) (\n - out

Re: [Haskell-cafe] adding recursion to a DSL

2013-02-19 Thread Edsko de Vries
Hi Joerg, You might find Abstract Syntax Graphs for Domain Specific Languages by Bruno Oliveira and Andres Löh ( http://ropas.snu.ac.kr/~bruno/papers/ASGDSL.pdf) a helpful reference to adding things like recursion (and other binding constructs) to your DSL. Edsko On Tue, Feb 19, 2013 at 9:47 AM

[Haskell-cafe] Parser left recursion

2013-02-19 Thread Martin Drautzburg
parser enters an infinite recursion, when I try to parse 1+2. I do understand why: hmm, this expression could be a plus, but then it must start with an expression, lets check. and it tries to parse expression again and again considers Plus. Twan van Laarhoven told me that: Left-recursion

Re: [Haskell-cafe] Parser left recursion

2013-02-19 Thread Roman Cheplyaka
* Martin Drautzburg martin.drautzb...@web.de [2013-02-20 08:13:16+0100] I do know for sure, that it is possible to parse (1+2)+3 (ghci does it just fine). But I seem to be missing a trick. Can anyone shed some light on this? The trick in this case is that ghci doesn't use a recursive

[Haskell-cafe] adding recursion to a DSL

2013-02-17 Thread fritsch
of the matrix and the third tuple element would represent the numbe of the row. For example 1 to 1. I want to achieve some sort of elegant (means readable code, a good representation) recursion that would let me do something like sequence [ out (matrixMult, A, n, row, matrix-row) | n - [1..1000

[Haskell-cafe] pragma to request tail recursion optimization (and perhaps [co]inductive recursion)

2012-10-25 Thread Petr P
Hi, Haskell compilers optimize tail recursive functions as cycles, which improves both memory and CPU complexity. However, it's easy to make a mistake and break the conditions under which a function can be tail recursive and thus optimized. Is there a way to tell a Haskell compiler that a

[Haskell-cafe] Is inspectable recursion in Arrows possible?

2012-10-01 Thread Alessandro Vermeulen
) returnA - (l+r) fibz - x Rewriting the function above to use a let statement compiles. However, here my second problem arises. I want to be able to inspect the recursion where it happens. However, in this case |fibz| is an infinite tree. I would like to capture

[Haskell-cafe] How to implement nested loops with tail recursion?

2012-09-19 Thread sdiyazg
I need to implement fast two-level loops, and I am learning using seq to make calls tail-recursive. I write programs to compute main = print $ sum [i*j|i::Int-[1..2],j::Int-[1..2]] This program (compiled with -O2) runs twenty times slower than the unoptimized (otherwise the loop gets

Re: [Haskell-cafe] How to implement nested loops with tail recursion?

2012-09-19 Thread sdiyazg
, 2012年 9 月 19日 下午 11:35:11 主题: How to implement nested loops with tail recursion? I need to implement fast two-level loops, and I am learning using seq to make calls tail-recursive. I write programs to compute main = print $ sum [i*j|i::Int-[1..2],j::Int-[1..2]] This program (compiled

Re: [Haskell-cafe] How to implement nested loops with tail recursion?

2012-09-19 Thread sdiyazg
] readIORef s=print Why? - 原始邮件 - 发件人: sdiy...@sjtu.edu.cn 收件人: haskell-cafe@haskell.org 发送时间: 星期四, 2012年 9 月 20日 上午 12:08:19 主题: Re: How to implement nested loops with tail recursion? Now I have discovered the right version... main = print (f 1 0::Int) where f i s = (if i=2 then (f (i

Re: [Haskell-cafe] How to implement nested loops with tail recursion?

2012-09-19 Thread Johan Tibell
On Wed, Sep 19, 2012 at 7:24 PM, sdiy...@sjtu.edu.cn wrote: main = do let f 0 acc = return acc f n acc = do v - return 1 f (n-1) (v+acc) f 100 100 = print Try this main = do let

Re: [Haskell-cafe] How to implement nested loops with tail recursion?

2012-09-19 Thread sdiyazg
readIORef s=print all overflows after correctly printing the first number - 原始邮件 - 发件人: Johan Tibell johan.tib...@gmail.com 收件人: sdiy...@sjtu.edu.cn 抄送: haskell-cafe@haskell.org 发送时间: 星期四, 2012年 9 月 20日 上午 1:28:47 主题: Re: [Haskell-cafe] How to implement nested loops with tail recursion

Re: [Haskell-cafe] How to implement nested loops with tail recursion?

2012-09-19 Thread Claude Heiland-Allen
Hi! On 19/09/12 19:00, sdiy...@sjtu.edu.cn wrote: So how do I force IO actions whose results are discarded (including IO ()) to be strict? () - foo :: IO () -- should work as it pattern matches, can wrap it in a prettier combinator !_ - foo :: IO a -- could work with -XBangPatterns I've not

Re: [Haskell-cafe] How to implement nested loops with tail recursion?

2012-09-19 Thread Johan Tibell
On Wed, Sep 19, 2012 at 8:00 PM, sdiy...@sjtu.edu.cn wrote: So how do I force IO actions whose results are discarded (including IO ()) to be strict? In your particular case it looks like you want Data.IORef.modifyIORef'. If your version of GHC doesn't include it you can write it like so: --

Re: [Haskell-cafe] Please help with double recursion

2011-05-30 Thread Richard O'Keefe
On 28/05/2011, at 11:47 PM, Dmitri O.Kondratiev wrote: Hello, I am trying to solve a simple task, but got stuck with double recursion - for some reason not all list elements get processed. Please advice on a simple solution, using plane old recursion :) *** Task: From a sequence

Re: [Haskell-cafe] Please help with double recursion

2011-05-30 Thread Dmitri O.Kondratiev
On Mon, May 30, 2011 at 11:26 AM, Richard O'Keefe o...@cs.otago.ac.nz wrote: On 28/05/2011, at 11:47 PM, Dmitri O.Kondratiev wrote: Hello, I am trying to solve a simple task, but got stuck with double recursion - for some reason not all list elements get processed. Please advice

[Haskell-cafe] Please help with double recursion

2011-05-28 Thread Dmitri O.Kondratiev
Hello, I am trying to solve a simple task, but got stuck with double recursion - for some reason not all list elements get processed. Please advice on a simple solution, using plane old recursion :) *** Task: From a sequence of chars build all possible chains where each chain consists of chars

[Haskell-cafe] Fwd: Please help with double recursion

2011-05-28 Thread Dmitri O.Kondratiev
For some reason, my previous message got truncated, so I repeat it in hope that it will come complete this time: -- Forwarded message -- From: Dmitri O.Kondratiev doko...@gmail.com Date: Sat, May 28, 2011 at 3:47 PM Subject: Please help with double recursion To: haskell-cafe

Re: [Haskell-cafe] Please help with double recursion

2011-05-28 Thread Daniel Fischer
On Saturday 28 May 2011 13:47:10, Dmitri O.Kondratiev wrote: Hello, I am trying to solve a simple task, but got stuck with double recursion - for some reason not all list elements get processed. Please advice on a simple solution, using plane old recursion :) *** Task: From a sequence

Re: [Haskell-cafe] Please help with double recursion

2011-05-28 Thread Dmitri O.Kondratiev
On Sat, May 28, 2011 at 3:57 PM, Daniel Fischer daniel.is.fisc...@googlemail.com wrote: On Saturday 28 May 2011 13:47:10, Dmitri O.Kondratiev wrote: Hello, I am trying to solve a simple task, but got stuck with double recursion - for some reason not all list elements get processed

Re: [Haskell-cafe] Please help with double recursion

2011-05-28 Thread Daniel Fischer
On Saturday 28 May 2011 14:19:18, Dmitri O.Kondratiev wrote: Thanks for simple and beautiful code to get all pairs. Yet, I need to get to the next step - from all pairs to build all chains, to get as a result a list of lists: [[abcde, acde, ade, ae,] [bcde, bde, be,] [cde, cd, ce,] de]]

Re: [Haskell-cafe] Please help with double recursion

2011-05-28 Thread wren ng thornton
On 5/28/11 8:31 AM, Daniel Fischer wrote: On Saturday 28 May 2011 14:19:18, Dmitri O.Kondratiev wrote: Thanks for simple and beautiful code to get all pairs. Yet, I need to get to the next step - from all pairs to build all chains, to get as a result a list of lists: [[abcde, acde, ade, ae,]

Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-17 Thread Tillmann Rendel
Hi, Daniel Fischer wrote: Let's look at the following code: countdown n = if n == 0 then 0 else foo (n - 1) s/foo/countdown/ presumably if' c t e = if c then t else e countdown' n = if' (n == 0) 0 (foo (n - 1)) s/foo/countdown'/ Yes to both substitutions. Looks like I

Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-17 Thread Daniel Fischer
On Thursday 17 March 2011 13:05:33, Tillmann Rendel wrote: Looks like I need an email client with ghc integration. That would be awesome. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-16 Thread Yves Parès
Hello, A question recently popped into my mind: does lazy evaluation reduce the need to proper tail-recursion? I mean, for instance : fmap f [] = [] fmap f (x:xs) = f x : fmap f xs Here fmap is not tail-recursive, but thanks to the fact that operator (:) is lazy, I think that it may still run

Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-16 Thread Tillmann Rendel
Hi, Yves Parès wrote: A question recently popped into my mind: does lazy evaluation reduce the need to proper tail-recursion? I mean, for instance : fmap f [] = [] fmap f (x:xs) = f x : fmap f xs Here fmap is not tail-recursive, but thanks to the fact that operator (:) is lazy, I think

Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-16 Thread Daniel Fischer
On Wednesday 16 March 2011 18:31:00, Yves Parès wrote: Hello, A question recently popped into my mind: does lazy evaluation reduce the need to proper tail-recursion? I mean, for instance : fmap f [] = [] fmap f (x:xs) = f x : fmap f xs Here fmap is not tail-recursive, but thanks

Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-16 Thread Yves Parès
daniel.is.fisc...@googlemail.com On Wednesday 16 March 2011 18:31:00, Yves Parès wrote: Hello, A question recently popped into my mind: does lazy evaluation reduce the need to proper tail-recursion? I mean, for instance : fmap f [] = [] fmap f (x:xs) = f x : fmap f xs Here fmap

Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-16 Thread Henning Thielemann
On Wed, 16 Mar 2011, Daniel Fischer wrote: Tail recursion is good for strict stuff, otherwise the above pattern - I think it's called guarded recursion - is better, have the recursive call as a non-strict field of a constructor. In http://haskell.org/haskellwiki/Tail_recursion it is also

Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-16 Thread Daniel Fischer
On Wednesday 16 March 2011 20:02:54, Yves Parès wrote: Yes, and a tail-recursive map couldn't run in constant space Yes, I meant if you are consuming it just once immediately. And that's what, to my knowledge, is impossible with tail recursion. A tail recursive map/fmap would have

Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-16 Thread Tillmann Rendel
()) Empty - Empty Here, the call to map is more visibly in tail position. According to the definition of tail recursion that I know, that's not tail recursive. My point is that the call to map is in tail position, because it is the last thing the function (\_ - map f xs ()) does

Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-16 Thread Yves Parès
And that's what, to my knowledge, is impossible with tail recursion. A tail recursive map/fmap would have to traverse the entire list before it could return anything. Now that you say it, yes, you are right. Tail recursion imposes strictness, since only the very last call can return something

Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-16 Thread Daniel Fischer
On Wednesday 16 March 2011 21:44:36, Tillmann Rendel wrote: My point is that the call to map is in tail position, because it is the last thing the function (\_ - map f xs ()) does. So it is not a tail-recursive call, but it is a tail call. Mmmm, okay, minor terminology mismatch, then.

Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-16 Thread Daniel Fischer
On Wednesday 16 March 2011 22:03:51, Yves Parès wrote: Can a type signature give you a hint about whether a function evaluates some/all of its arguments (i.e. is strict/partially strict/lazy), or do you have to look at the implementation to know? Cheating, with GHC, a magic hash tells you it's

Re: [Haskell-cafe] Parsec-like parser combinator that handles left recursion?

2009-12-10 Thread Nils Anders Danielsson
On 2009-12-10 07:16, o...@okmij.org wrote: There are at least two parser combinator libraries that can deal with *any* left-recursive grammars. Parser combinators are often used to describe infinite grammars (with a finite number of parametrised non-terminals). The library described by Frost

Re: [Haskell-cafe] Parsec-like parser combinator that handles left recursion?

2009-12-09 Thread Nils Anders Danielsson
On 2009-12-08 16:11, S. Doaitse Swierstra wrote: In principle it is not possible to parse left-recursive grammars [...] I suspect that this statement is based on some hidden assumption. It /is/ possible to parse many left recursive grammars using parser combinators, without rewriting the

Re: [Haskell-cafe] Parsec-like parser combinator that handles left recursion?

2009-12-09 Thread Dan Doel
parsing expression grammars, and the relevant paper Packrat Parsers can Support Left Recursion. (Your parsers aren't PEGs, are they? If so, I apologize for the redundancy.) There's a PEG parser combinator library written by John Meacham (of jhc fame), named Frisby (there's also pappy, but it's

Re: [Haskell-cafe] Parsec-like parser combinator that handles left recursion?

2009-12-09 Thread Nils Anders Danielsson
On 2009-12-09 18:50, Dan Doel wrote: (Your parsers aren't PEGs, are they? If so, I apologize for the redundancy.) No, my parsers use Brzozowski derivatives. See the related work section of the paper I mentioned for some other parser combinator libraries which can handle (some) left recursive

[Haskell-cafe] Parsec-like parser combinator that handles left recursion?

2009-12-09 Thread oleg
There are at least two parser combinator libraries that can deal with *any* left-recursive grammars. That said, Prof. Swierstra's advice to try to get rid of left recursion is still well worth to follow. The first library is described in Frost, Richard, Hafiz, Rahmatullah, and Callaghan

[Haskell-cafe] Parsec-like parser combinator that handles left recursion?

2009-12-08 Thread Adam Cigánek
Hello there, Is there some other parser library, with similar nice API than Parsec, but which somehow handles left-recursive grammars? Ideally if it has at least rudimentary documentation and/or tutorial :) ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Parsec-like parser combinator that handles left recursion?

2009-12-08 Thread John A. De Goes
X-Saiga. Regards, John On Dec 8, 2009, at 7:10 AM, Adam Cigánek wrote: Hello there, Is there some other parser library, with similar nice API than Parsec, but which somehow handles left-recursive grammars? Ideally if it has at least rudimentary documentation and/or tutorial :)

[Haskell-cafe] buildExpressionParser prefix recursion

2009-12-01 Thread Warren Harris
I was wondering why Parsec's buildExpressionParser doesn't allow prefix expressions to be handled recursively, e.g. given a prefix ! operation, it seems that !!a could parse without requiring parentheses (!(!a)). Is there an easy way to extend it? (I have a rich expression grammar I'd like

[Haskell-cafe] tail recursion

2009-04-07 Thread Daryoush Mehrtash
Is the call to go in the following code considered as tail recursion? data DList a = DLNode (DList a) a (DList a) mkDList :: [a] - DList a mkDList [] = error http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:error must have at least one element mkDList xs = let (first,last

Re: [Haskell-cafe] tail recursion

2009-04-07 Thread wren ng thornton
Daryoush Mehrtash wrote: Is the call to go in the following code considered as tail recursion? data DList a = DLNode (DList a) a (DList a) mkDList :: [a] - DList a mkDList [] = error must have at least one element mkDList xs = let (first,last) = go last xs first in first

Re: [Haskell-cafe] Re: A guess on stack-overflows - thunks build-up andtail recursion

2009-03-30 Thread Claus Reinke
of the operation being folded. It is the association of everything to one side, for a strict operation, that leads to an expression whose evaluation will run out of limited stack, while storing the arguments not yet used on the other side. If your operation is associative, you could unroll the recursion

Re: [Haskell-cafe] Re: A guess on stack-overflows - thunksbuild-upandtail recursion

2009-03-22 Thread Claus Reinke
to observe the effects we're interested in, two files are sufficient, and large input files would only obscure the animation): $ cat a b a1 a2 a3 b1 b2 b3 2. tail recursion and strictness, if an external data structure is in the way Taking Data.IntMap as an example, because it tends to come up often

[Haskell-cafe] Re: A guess on stack-overflows - thunks build-up and tail recursion

2009-03-21 Thread G?uenther Schmidt
Hi Bas, I'd like to share some thoughts with you. Let's say I'm unable, for whatever reason, to force full evaluation of the accumulator during a foldl. So I have this huge build up of thunks, which causes a stack overflow when the thunks are being reduced. I wonder if I could write some

[Haskell-cafe] A guess on stack-overflows - thunks build-up and tail recursion

2009-03-20 Thread GüŸnther Schmidt
Hi all, I've been running into stack-overflow problems for some time now. Here is what I gathered so far. I used to think that the build up of thunks caused the stack overflow when, as it turns out, it does not. I apparently can have a huge thunk build up eventhough I use a supposedly

Re: [Haskell-cafe] A guess on stack-overflows - thunks build-up and tail recursion

2009-03-20 Thread Bas van Dijk
On Fri, Mar 20, 2009 at 11:59 AM, GüŸnther Schmidt gue.schm...@web.de wrote: I apparently can have a huge thunk build up eventhough I use a supposedly accumulative, tail-recursive algorithm. This is correct. If you don't strictly evaluate your accumulator before you tail recursive, a thunk will

Re: [Haskell-cafe] A guess on stack-overflows - thunks build-up and tail recursion

2009-03-20 Thread Ketil Malde
GüŸnther Schmidt gue.schm...@web.de writes: Apparently it is the evaluation of this huge build-up that causes the stack-overflow but not the thunk-build-up *as such*. Do I understand this correctly? I think that is correct. Prelude foldl (+) 0 [1..100] *** Exception: stack overflow

[Haskell-cafe] Re: A guess on stack-overflows - thunks build-up and tail recursion

2009-03-20 Thread GüŸnther Schmidt
Thanks Bas and Ketil, the point I wanted to stress though is that the stack overflow does actually not occur doing the recursive algorithm, just a build-up of thunks. The algorithm itself will eventually complete without the stack overflow. The problem occurs when the result value is needed

Re: [Haskell-cafe] Re: A guess on stack-overflows - thunks build-up and tail recursion

2009-03-20 Thread Edsko de Vries
The problem occurs when the result value is needed and thus the thunks need to be reduced, starting with the outermost, which can't be reduced without reducing the next one etc and it's these reduction steps that are pushed on the stack until its size cause a stack-overflow. Yes,

[Haskell-cafe] Re: A guess on stack-overflows - thunks build-up and tail recursion

2009-03-20 Thread GŸuenther Schmidt
Thanks Bas and Ketil, the point I wanted to stress though is that the stack overflow does actually not occur doing the recursive algorithm, just a build-up of thunks. The algorithm itself will eventually complete without the stack overflow. The problem occurs when the result value is needed

Re: [Haskell-cafe] Re: A guess on stack-overflows - thunks build-up and tail recursion

2009-03-20 Thread Bas van Dijk
On Fri, Mar 20, 2009 at 2:01 PM, GüŸnther Schmidt gue.schm...@web.de wrote: The problem occurs when the result value is needed and thus the thunks need to be reduced, starting with the outermost, which can't be reduced without reducing the next one etc and it's these reduction steps that

Re: [Haskell-cafe] Re: A guess on stack-overflows - thunks build-upand tail recursion

2009-03-20 Thread Claus Reinke
The problem occurs when the result value is needed and thus the thunks need to be reduced, starting with the outermost, which can't be reduced without reducing the next one etc and it's these reduction steps that are pushed on the stack until its size cause a stack-overflow. Yes,

Re: [Haskell-cafe] Re: A guess on stack-overflows - thunks build-up and tail recursion

2009-03-20 Thread Matthew Brecknell
GüŸnther Schmidt wrote: the point I wanted to stress though is that the stack overflow does actually not occur doing the recursive algorithm, just a build-up of thunks. You can also observe this with suitable trace statements. For example: import Debug.Trace import System.Environment

[Haskell-cafe] Forcing evaluation when seq or strictness annotation are not possible [was: guess on stack-overflows - thunks build-up and tail recursion]

2009-03-20 Thread Gü?nther Schmidt
Hi all, here I am again with my all time favorite unsolved problem: stack overflows. The advice I have received so far from the Haskell community (this list and #haskell) was to use strictness annotation or seq in most cases. And indeed it did help. It certainly helped when I used a data

Re: [Haskell-cafe] Re: A guess on stack-overflows - thunks build-upand tail recursion

2009-03-20 Thread Don Stewart
It would be great to have a video of this in action up on youtube. You can simply 'recordmydesktop' on linux (and likely elsewhere), then upload the result. It also helps the general adoption cause, having Haskell more visible and accessible. claus.reinke: The problem occurs when the result

Re: [Haskell-cafe] Re: A guess on stack-overflows - thunksbuild-upand tail recursion

2009-03-20 Thread Claus Reinke
It would be great to have a video of this in action up on youtube. You can simply 'recordmydesktop' on linux (and likely elsewhere), then upload the result. I'm curious: how would a non-interactive animation running in Flash in a browser be better than an interactive animation running in Java

Re: [Haskell-cafe] Re: A guess on stack-overflows - thunks build-up and tail recursion

2009-03-20 Thread wren ng thornton
the evaluation across the recursion which ensures that peak stack usage is always within bounds. For the data constructor example above, using a strict fold is not a win because it means you necessarily force the entire data structure, even though you may only need a portion

Re: [Haskell-cafe] Re: A guess on stack-overflows - thunksbuild-upand tail recursion

2009-03-20 Thread Duane Johnson
I just found out about GHood through this thread, and since it impressed me very much to see something so cool, I feel bad making this comment... but I am always disturbed by the flickering effect produced by java applets in my browser (FF 3.0) while scrolling. From an implementation

[Haskell-cafe] Horner's Rule, foldl, and direct recursion

2009-03-10 Thread R J
Given a list of decimal digits represented by Integers between 0 and 9--for example, the list [1,2,3, 4]--with the high-order digit at the left, the list can be converted to a decimal integer n using the following formula, an instance of Horner's rule: n = 10 * 10 * 10 * 1 + 10

Re: [Haskell-cafe] Horner's Rule, foldl, and direct recursion

2009-03-10 Thread Daniel Fischer
Am Mittwoch, 11. März 2009 00:58 schrieb R J: Given a list of decimal digits represented by Integers between 0 and 9--for example, the list [1,2,3, 4]--with the high-order digit at the left, the list can be converted to a decimal integer n using the following formula, an instance of Horner's

[Haskell-cafe] Stack Overflow, tail recursion and CPS

2009-01-14 Thread Günther Schmidt
Hi all, I get a stack overflow when I want to insert a huge, lazy list into a Map. I have changed the insertion algo to use foldl to make it tail-recursive but still get a stack overflow as the insert remains lazy. Could CPS be a solution in these cases? Günther

Re: [Haskell-cafe] Stack Overflow, tail recursion and CPS

2009-01-14 Thread Günther Schmidt
Hi Eugene, tried that, but since the action to be evaluated is the insertion into a structure that won't work. The strictness here doesn't go deep enough, it stopps short. Günther Am 14.01.2009, 18:27 Uhr, schrieb Eugene Kirpichov ekirpic...@gmail.com: Use foldl' ? 2009/1/14 Günther

Re: [Haskell-cafe] Stack Overflow, tail recursion and CPS

2009-01-14 Thread Neil Mitchell
Hi I have changed the insertion algo to use foldl to make it tail-recursive but still get a stack overflow as the insert remains lazy. Try foldl' and insertWith' - that should work. Thanks Neil ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Stack Overflow, tail recursion and CPS

2009-01-14 Thread Günther Schmidt
Hello Neil, thanks, that did indeed work. I guess I shot myself in the foot a bit here ... Cause my real problem isn't actually with Map but with IxSet (from HAppS) which to my knowledge does not have some sort of strict insert function. Me trying to be really clever just used Map as a

Re: [Haskell-cafe] Stack Overflow, tail recursion and CPS

2009-01-14 Thread Jonathan Cast
On Wed, 2009-01-14 at 19:19 +0100, Günther Schmidt wrote: Hello Neil, thanks, that did indeed work. I guess I shot myself in the foot a bit here ... Cause my real problem isn't actually with Map but with IxSet (from HAppS) which to my knowledge does not have some sort of strict insert

[Haskell-cafe] Writing a function isPrime using recursion.

2008-10-15 Thread Kalashnikov
I'm supposed to write a function isPrime that checks whether or not a given integer is a prime number or not. The function has to use recursion. The only advice I was given, was to use a helper function. I still have no clue how to do it :confused: I'm new to Haskell by the way..please help

Re: [Haskell-cafe] Writing a function isPrime using recursion.

2008-10-15 Thread Bulat Ziganshin
Hello Kalashnikov, Thursday, October 16, 2008, 2:41:05 AM, you wrote: I'm supposed to write a function isPrime that checks whether or not a given integer is a prime number or not. The function has to use recursion. The only advice I was given, was to use a helper function. seems that russian

Re: [Haskell-cafe] Writing a function isPrime using recursion.

2008-10-15 Thread Nathan Bloomfield
At the risk of doing someone's homework... A naive solution is to do trial division by all integers from 2 up to sqrt n. {- isPrime :: Integer - BoolisPrime n | n 2 = False | otherwise = f 2 n where f k n = if k isqrt then True else undefined -- exercise for the reader -}

Re: [Haskell-cafe] Re: Understanding tail recursion and trees

2008-05-03 Thread David Menendez
On Thu, May 1, 2008 at 4:10 PM, Daniil Elovkov [EMAIL PROTECTED] wrote: Felipe Lessa wrote: On Thu, May 1, 2008 at 9:44 AM, Felipe Lessa [EMAIL PROTECTED] wrote: On Thu, May 1, 2008 at 9:32 AM, Edsko de Vries [EMAIL PROTECTED] wrote: So then the question becomes: what *is* the

  1   2   3   >