Re: [Haskell-cafe] Updating doubly linked lists

2008-12-31 Thread Martijn van Steenbergen
Hi Stephan, S. Günther wrote: Is it possible to change a particular node of the doubly linked list? That is to say, that would like to have a function: update :: DList a - a - DList a where update node newValue returns a list where only the value at the node which is passed in is set to the new

[Haskell-cafe] about the concatenation on a tree

2008-12-31 Thread Max cs
hi all, not sure if there is someone still working during holiday like me : ) I got a little problem in implementing some operations on tree. suppose we have a tree date type defined: data Tree a = Leaf a | Branch (Tree a) (Tree a) I want to do a concatenation on these tree just like the

Re: [Haskell-cafe] about the concatenation on a tree

2008-12-31 Thread Emil Axelsson
I'm not working, but still checking mail. If you don't care about balancing the tree or the order of elements, you can just use Branch :: Tree a - Tree a - Tree a as a concatenation operator. Check with GHCi to see that the Branch constructor actually has the above type. / Emil Max

[Haskell-cafe] Re: [Haskell-beginners] about the concatenation on a tree

2008-12-31 Thread Thomas Davie
On 31 Dec 2008, at 16:02, Max cs wrote: hi all, not sure if there is someone still working during holiday like me : ) I got a little problem in implementing some operations on tree. suppose we have a tree date type defined: data Tree a = Leaf a | Branch (Tree a) (Tree a) I want to do a

Re: [Haskell-cafe] Gitit - Encoding

2008-12-31 Thread Conal Elliott
Aside: lookPairs :: RqData [(String,String)] lookPairs = asks fst = return . map (\(n,vbs)-(n,L.unpack $ inputValue vbs)) Looks like an opportunity for semantic editor combinators [1]. Something like lookPairs = (fmap.fmap.fmap) (L.unpack . inputValue) (asks fst) Or specialize the edit

Re: [Haskell-cafe] about the concatenation on a tree

2008-12-31 Thread Henk-Jan van Tuyl
Forgot to send this to the list. On Wed, 31 Dec 2008 16:05:10 +0100, Max cs max.cs.2...@googlemail.com wrote: hi all, not sure if there is someone still working during holiday like me : ) I got a little problem in implementing some operations on tree. suppose we have a tree date type

[Haskell-cafe] Will GHC finally support epoll in 2009?

2008-12-31 Thread Levi Greenspan
Ticket #635 Replace use of select() in the I/O manager with epoll/kqueue/etc. (http://hackage.haskell.org/trac/ghc/ticket/635) dates back from 2005. Now its 2009 and GHC can handle hundreds of thousands of threads, yet having more than 1024 file descriptors open is still impossible. This

Re: [Haskell-cafe] about the concatenation on a tree

2008-12-31 Thread Henk-Jan van Tuyl
On Wed, 31 Dec 2008 17:19:09 +0100, Max cs max.cs.2...@googlemail.com wrote: Hi Henk-Jan van Tuyl, Thank you very much for your reply! I think the concatenation should be different to thhe treeConcat :: Tree a - Tree a - Tree a the above is a combination of two trees instead of a

Re: [Haskell-cafe] about the concatenation on a tree

2008-12-31 Thread Thomas Davie
On 31 Dec 2008, at 21:18, Henk-Jan van Tuyl wrote: On Wed, 31 Dec 2008 17:19:09 +0100, Max cs max.cs. 2...@googlemail.com wrote: Hi Henk-Jan van Tuyl, Thank you very much for your reply! I think the concatenation should be different to thhe treeConcat :: Tree a - Tree a - Tree a the

[Haskell-cafe] WriterT [w] IO is not lazy in reading [w]

2008-12-31 Thread Paolino
As someone suggested me, I can read the logs from Writer and WriterT as computation goes by, if the monoid for the Writer is lazy readable. This has been true until I tried to put the IO inside WriterT {-# LANGUAGE FlexibleContexts #-} import Control.Monad.Writer k :: (MonadWriter [Int] m) =

Re: [Haskell-cafe] about the concatenation on a tree

2008-12-31 Thread Henk-Jan van Tuyl
On Wed, 31 Dec 2008 21:25:02 +0100, Thomas Davie tom.da...@gmail.com wrote: On 31 Dec 2008, at 21:18, Henk-Jan van Tuyl wrote: On Wed, 31 Dec 2008 17:19:09 +0100, Max cs max.cs.2...@googlemail.com wrote: Hi Henk-Jan van Tuyl, Thank you very much for your reply! I think the

Re: [Haskell-cafe] WriterT [w] IO is not lazy in reading [w]

2008-12-31 Thread Derek Elkins
On Wed, 2008-12-31 at 21:48 +0100, Paolino wrote: As someone suggested me, I can read the logs from Writer and WriterT as computation goes by, if the monoid for the Writer is lazy readable. This has been true until I tried to put the IO inside WriterT {-# LANGUAGE FlexibleContexts #-}

Re: [Haskell-cafe] WriterT [w] IO is not lazy in reading [w]

2008-12-31 Thread Ryan Ingram
IO is not lazy; you never make it to print. Consider this program: k = f 0 where f n = do lift (print n) tell [n] f (n+1) weird :: IO [Int] weird = do (_, ns) - runWriterT k return (take 20 ns) What should weird print? According to k, it prints every

Re: [Haskell-cafe] Updating doubly linked lists

2008-12-31 Thread Ryan Ingram
Also, it's actually really hard to tie the knot in the update; without some kind of distinguished node that allows you to know that it is the beginning/end of the list. For example, in this DList: 1,1,1, lots of times, 1, 2, 1, 1, ... lots of times, 1, (loop) If you change the 3rd 1, how

[Haskell-cafe] bottom case in proof by induction

2008-12-31 Thread raeck
Dear all, Happy New Year! I am learning the Induction Proof over Haskell, I saw some proofs for the equivalence of two functions will have a case called 'bottom' but some of them do no have. What kind of situation we should also include the bottom case to the proof? How about the functions

Re: [Haskell-cafe] bottom case in proof by induction

2008-12-31 Thread Luke Palmer
2008/12/31 ra...@msn.com Dear all, Happy New Year! I am learning the Induction Proof over Haskell, I saw some proofs for the equivalence of two functions will have a case called 'bottom' but some of them do no have. What kind of situation we should also include the bottom case to the

[Haskell-cafe] ANN: monte-carlo-0.2, gsl-random-0.2.3

2008-12-31 Thread Patrick Perry
I've released a new version of the monte-carlo packages for haskell. Here are the highlights for monte-carlo: Changes in 0.2: * More general type class, MonadMC, which allows all the functions to work in both MC and MCT monads. * Functions to sample from discrete distributions. *

Re: [Haskell-cafe] bottom case in proof by induction

2008-12-31 Thread Martijn van Steenbergen
Luke Palmer wrote: First, by simple definition, id _|_ = _|_. Now let's consider foo _|_. The Haskell semantics say that pattern matching on _|_ yields _|_, so foo _|_ = _|_. So they are equivalent on _|_ also. Thus foo and id are exactly the same function. Would it in general also be

Re: [Haskell-cafe] bottom case in proof by induction

2008-12-31 Thread Derek Elkins
On Thu, 2009-01-01 at 02:16 +0100, Martijn van Steenbergen wrote: Luke Palmer wrote: First, by simple definition, id _|_ = _|_. Now let's consider foo _|_. The Haskell semantics say that pattern matching on _|_ yields _|_, so foo _|_ = _|_. So they are equivalent on _|_ also. Thus foo

Re: [Haskell-cafe] Updating doubly linked lists

2008-12-31 Thread S. Günther
Thanks for the answers to all. Untying the knot was (and still is) exactly the problem I was facing. I knew that the whole list had to be rebuild and wasn't concerned with performance since at that point I just wanted to know how to do it and if it is possible at all. After I realized that it

Re: [Haskell-cafe] bottom case in proof by induction

2008-12-31 Thread raeck
I am afraid I am still confused. foo [] = ... foo (x:xs) = ... There is an implied: foo _|_ = _|_ The right side cannot be anything but _|_. If it could, then that would imply we could solve the halting problem: in a proof, how I could say the right side must be _|_ without defining foo

Re: [Haskell-cafe] bottom case in proof by induction

2008-12-31 Thread Jonathan Cast
On Thu, 2009-01-01 at 03:50 +, ra...@msn.com wrote: I am afraid I am still confused. foo [] = ... foo (x:xs) = ... There is an implied: foo _|_ = _|_ The right side cannot be anything but _|_. If it could, then that would imply we could solve the halting problem: in a

Re: [Haskell-cafe] bottom case in proof by induction

2008-12-31 Thread Daniel Fischer
Am Donnerstag, 1. Januar 2009 04:50 schrieb ra...@msn.com: I am afraid I am still confused. foo [] = ... foo (x:xs) = ... There is an implied: foo _|_ = _|_ The right side cannot be anything but _|_. If it could, then that would imply we could solve the halting problem: in a

Re: [Haskell-cafe] bottom case in proof by induction

2008-12-31 Thread Derek Elkins
On Wed, 2008-12-31 at 22:08 -0600, Jonathan Cast wrote: On Thu, 2009-01-01 at 03:50 +, ra...@msn.com wrote: I am afraid I am still confused. foo [] = ... foo (x:xs) = ... There is an implied: foo _|_ = _|_ The right side cannot be anything but _|_. If it could, then that

[Haskell-cafe] ANN: gitit-0.4.1, recaptcha-0.1

2008-12-31 Thread John MacFarlane
I'm pleased to announce the release of gitit-0.4.1, which I've just uploaded to HackageDB. Gitit is a wiki program that stores pages in a git repostory. Gitit now has support for (optional) captchas, using the reCAPTCHA service. I've packaged up the reCAPTCHA code as a separate library on

Re: [Haskell-cafe] WriterT [w] IO is not lazy in reading [w]

2008-12-31 Thread Paolino
I must ask why runWriterT k :: State s (a,[Int]) is working. Looks like I could runIO the same way I evalState there. In that case I wouldn't wait for the State s action to finish. Thanks 2008/12/31 Derek Elkins derek.a.elk...@gmail.com On Wed, 2008-12-31 at 21:48 +0100, Paolino wrote: As

Re: [Haskell-cafe] WriterT [w] IO is not lazy in reading [w]

2008-12-31 Thread Paolino
How do I read IO is not lazy ? Is IO (=) forcing the evaluation of its arguments, causing the unwanted neverending loop? And, this happens even in (MonadTrans t = t IO) (=) ? Thanks paolino 2008/12/31 Ryan Ingram ryani.s...@gmail.com IO is not lazy; you never make it to print. Consider

[Haskell-cafe] definition of data

2008-12-31 Thread Max.cs
hi all, I want to define a data type Tree a that can either be a or Branch (Tree a) (Tree a)? I tried data Tree a = a | Branch (Tree a) (Tree a) deriving Show but it seems not accpetable in haskell ? any way I could achieve this ? Thanks

Re: [Haskell-cafe] definition of data

2008-12-31 Thread Brandon S. Allbery KF8NH
On 2009 Jan 1, at 2:32, Max.cs wrote: data Tree a = a | Branch (Tree a) (Tree a) deriving Show but it seems not accpetable in haskell ? You need a constructor in both legs of the type: data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving Show -- brandon s. allbery

Re: [Haskell-cafe] definition of data

2008-12-31 Thread Adrian Neumann
You need some type constructor: data Tree a = Leaf a | Branch (Tree a) (Tree a) Am 01.01.2009 um 08:32 schrieb Max.cs: hi all, I want to define a data type Tree a that can either be a or Branch (Tree a) (Tree a)? I tried data Tree a = a | Branch (Tree a) (Tree a) deriving Show but it