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 Value and
all other values are the same. All this of course
in a pure way, that is without using (M/T/TM)Vars
or IORefs.


The short answer is: yes, but the complete DList structure will need to 
be built anew (if nodes in the updated list are needed).


The longer answer is: Because everything is pure, 'update' will need to 
create a new DLNode with the new value. But then you will also want to 
update the node's neighbours to point to the newly created DLNode, 
because if you don't then moving forward and then backward one position 
would make you end up at the old value again. But to update the 
neighbours' links to the new node you need to create new neighbour 
DLNodes, because everything is pure. And so on, until the whole list has 
been recreated.


To not need to recreate the whole list you will need some kind of 
assignment, and this is exactly what vars/refs are for.


Hope this helps,

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


[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 concat on list.
Anyone has idea on it? or there are some existing implementation?

Thank you and Happy New Year!

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


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 cs skrev:
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 concat on list.

Anyone has idea on it? or there are some existing implementation?
 
Thank you and Happy New Year!
 
regards,

Max




___
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] 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 concatenation on these tree just like the concat on  
list.

Anyone has idea on it? or there are some existing implementation?

Thank you and Happy New Year!



How would you like to concatenate them?  Concatonation on lists is  
easy because there's only one end point to attach the next list to, on  
a tree though, there are many leaves to attach things to.


Here's a few examples though:
Attaching to the right most point on the tree (tree data structure  
modified to store data in branches not leaves here)


data Tree a = Leaf | Branch (Tree a) a (Tree a)

concatT :: [Tree a] - Tree a
concatT = foldr1 appendT

appendT :: Tree a - Tree a - Tree a
appendT Leaf t = t
appendT (Branch l x r) t = Branch l x (appendT r t)

Attaching to *all* the leaves on the tree (same modification to the  
data structure)


concatT :: [Tree a] - Tree a
concatT = foldr1 appendT

appendT :: Tree a - Tree a - Tree a
appendT Leaf t = t
appendT (Branch l x r) t = Branch (appendT l t) x (appendT r t)

merging a list of trees maintaining them as ordered binary trees

concatT :: Ord a = [Tree a] - Tree a
concatT = foldr1 unionT

unionT :: Ord a = Tree a - Tree a - Tree a
unionT t = foldrT insertT t

foldrT :: (a - b - b) - b - Tree a - b
foldrT f z Leaf = z
foldrT f z (Branch l x r) = f x (foldrT f (foldrT f z r) l)

insertT :: Ord a = a - Tree a - Tree a
insertT x Leaf = Branch Leaf x Leaf
insertT x (Branch l y r)
  | x = y = Branch (insertT x l) y r
  | otherwise = Branch l y (insertT x r)

Hope that helps.

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


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 path to (fmap.map.second) .

   - Conal

[1] http://conal.net/blog/semantic-editor-combinators

On Tue, Dec 30, 2008 at 6:14 AM, Jeremy Shaw jer...@n-heptane.com wrote:

 Hello,

 I have not looked at the gitit source code, but I have had this
 problem in other HAppS applications. The problem is that by default
 HAppS does nothing about string encodings. The easy fix is to use
 utf-8 and unicode everywhere. ('easy' compared to supporting multiple
 encodings).

 The goal is to make sure that in gitit, a String is always a list of
 unicode code points, and not a list of utf-8 encoded octets. This
 means that whenever data comes in or goes out of gitit it needs to be
 decoded or encoded.

 To transition you need to do atleast the following:

 1. Set the charset of the outgoing pages so that the browser knows
 that the pages is supposed to be utf-8:

  For html, this can be done by adding this meta to the head of each page:

  meta http-equiv=Content-Type content=text/html; charset=UTF-8

  However, for text/plain, etc, you must set it in the HTTP header
  (which I will cover later). For html, it is still useful to set the
  meta tag though, so that if the page is saved to disk, the encoding
  is not lost.

 2. use the utf8-string library, and make sure that all the
 inputs/outputs are decoded/encoded properly.

 This probably means patching your copy of HAppS-Server (or copying the
 modified functions into gitit).

 For example, lookPairs currently looks like this:

  lookPairs :: RqData [(String,String)]
  lookPairs = asks fst = return . map (\(n,vbs)-(n,L.unpack $ inputValue
 vbs))

 As you can see, it just takes the incoming bytes and converts them to
 a String, but without doing any decoding. You probably want something
 more like:

  lookPairs :: RqData [(String,String)]
  lookPairs = asks fst = return . map
 (\(n,vbs)-(n,Data.ByteString.Lazy.UTF8.toString $ inputValue vbs))

 Some of the other look* functions need patching as well.

 Similarily, the ToMessage instances need to encode the outgoing data.
 Consider:

  instance ToMessage Html where
 toContentType _ = B.pack text/html
 toMessage = L.pack . renderHtml

 We really want to make two changes:

  instance ToMessage Html where
 toContentType _ = B.pack text/html; charset=UTF-8-- add
 the encoding
 toMessage = Data.ByteString.Lazy.UTF8.fromString . renderHtml  --
 encode the data

 3. make sure that any I/O (readFile, writeFile, etc) uses the utf-8
 functions from utf8-string.

 If you don't want to patch HAppS-Server, then you could work around it by
 doing silliness like:

  do pairs' - lookPairs
let pairs = map (first toString . second toString) pairs'

 but that seems error prone and not a long term solution. The obvious
 long term solution is for HAppS to fix its encoding issues. The simple
 fix is to hardwire it for utf-8, but a system that would supports
 arbitrary encodings might be nice?

 As far as I know, no one has even tried to submit a patch hardwiring
 HAppS to use utf-8 -- which seems like a good short-term solution. You
 might try posting on the HAppS mailing list and see if such a patch
 would be welcome:

 http://groups.google.com/group/HAppS

 hope this helps.
 - jeremy


 At Tue, 30 Dec 2008 13:58:15 +0100,
 Arnaud Bailly wrote:
 
  Hello,
  I have started using Gitit and I am very happy with it and eager to
  start hacking. I am running into a practical problem: characters
  encoding. When I edit pages using accented characters (I am french),
  the accents get mangled when the page come back from server.
 
  The raw files are incorrectly encoded. Where Shall I look for fixing
  this issue ?
 
  Thanks
 
  ps: the wiki is live at http://www.notre-ecole.org(some of the other
 look funct
 
  --
  Arnaud Bailly, PhD
  OQube - Software Engineering
 
  web http://www.oqube.com
  ___
  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] 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 defined:

data Tree a = Leaf a | Branch (Tree a) (Tree a)

I want to do a concatenation on these tree just like the concat on list.
Anyone has idea on it? or there are some existing implementation?

Thank you and Happy New Year!

regards,
Max


Hi Max,

A simple way to do this:


module TreeConcat where



data Tree a = Leaf a | Branch (Tree a) (Tree a)
  deriving Show



treeConcat :: Tree a - Tree a - Tree atreeConcat xs ys = Branch xs ys



main :: IO ()
main = print $ treeConcat (Leaf 1) (Leaf 2)


But perhaps you want a certain ordering? Have a look at:

http://hackage.haskell.org/packages/archive/AvlTree/4.2/doc/html/Data-Tree-AVL.html#44


--
Regards,
Henk-Jan van Tuyl


--
http://functor.bamikanarie.com
http://Van.Tuyl.eu/
--

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


[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 limitation is a real bottle neck and
prevents some cool developments on server side, like scalable comet
servers. Instead others (e.g. Erlang guys) post stories about how they
achived 1 million comet users (cf.
http://www.metabrew.com/article/a-million-user-comet-application-with-mochiweb-part-1/
).

Hence my question - is it likely that GHC will support epoll in 2009?

Cheers and happy new year!

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


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 concatenation, so
I think the type of treeConcat should be:

treeConcat :: Tree (Tree a) - Tree a

instead. How do you think? : ) I tried to implement it .. but it seems
confusing.. to me

Thanks

Max


Hello Max,

The function
  treeConcat :: Tree (Tree a) - Tree a
cannot be created, as it has an infinite type;
you can however, define a function that replaces leafs with trees,
for example treeConcat' in the following module, that replaces all leaves  
that contains a one with a given tree:



module TreeConcat where



data Tree a = Leaf a | Branch (Tree a) (Tree a)
  deriving Show



treeConcat' :: Num a = Tree a - Tree a - Tree a
treeConcat' (Leaf 1) tree = tree
treeConcat' (Leaf x) _= Leaf x
treeConcat' (Branch x y) tree = Branch (treeConcat' x tree) (treeConcat'  
y tree)



main :: IO ()
main = print $ treeConcat' (Branch (Leaf 1) (Leaf 2)) (Branch (Leaf 3)  
(Leaf 4))


This displays:
  Branch (Branch (Leaf 3) (Leaf 4)) (Leaf 2)

If this doen't help you either, I need to know more about what you are  
trying to do.


Regards,
Henk-Jan van Tuyl


--
http://functor.bamikanarie.com
http://Van.Tuyl.eu/
--





On Wed, Dec 31, 2008 at 3:33 PM, Henk-Jan van Tuyl  
hjgt...@chello.nlwrote:



Hi Max,

A simple way to do this:

 module TreeConcat where




 data Tree a = Leaf a | Branch (Tree a) (Tree a)

 deriving Show



 treeConcat :: Tree a - Tree a - Tree atreeConcat xs ys = Branch xs ys




 main :: IO ()

main = print $ treeConcat (Leaf 1) (Leaf 2)



But perhaps you want a certain ordering? Have a look at:

http://hackage.haskell.org/packages/archive/AvlTree/4.2/doc/html/Data-Tree-AVL.html#44


--
Regards,
Henk-Jan van Tuyl


--
http://functor.bamikanarie.com
http://Van.Tuyl.eu/
--







--

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


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 above is a combination of two trees instead of a concatenation,  
so

I think the type of treeConcat should be:

treeConcat :: Tree (Tree a) - Tree a

instead. How do you think? : ) I tried to implement it .. but it  
seems

confusing.. to me

Thanks

Max


Hello Max,

The function
 treeConcat :: Tree (Tree a) - Tree a
cannot be created, as it has an infinite type;


It does?  How did he type it then?  And yes, it can be created
concatT :: Tree (Tree a) - Tree a
concatT (Leaf t) = t
concatT (Branch l r) = Branch (concatT l) (concatT r)

It's also known as join on trees (as I explained a bit more in my  
response on haskell-beginners).


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


[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) = m [Int]
 k = let f x = tell [x]  f (x + 1) in f 0

 works :: [Int]
 works = snd $ runWriter k

 hangs :: IO [Int]
 hangs = snd `liftM` runWriterT k

 main = take 20 `liftM` hangs = print


The main hangs both interpreted and compiled on ghc 6.10.1.

The issue is not exposing with IO alone as

main = print test  main

is a working program.

Thanks for explanations.

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


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 concatenation should be different to thhe

treeConcat :: Tree a - Tree a - Tree a

the above is a combination of two trees instead of a concatenation, so
I think the type of treeConcat should be:

treeConcat :: Tree (Tree a) - Tree a

instead. How do you think? : ) I tried to implement it .. but it seems
confusing.. to me

Thanks

Max


Hello Max,

The function
 treeConcat :: Tree (Tree a) - Tree a
cannot be created, as it has an infinite type;


It does?  How did he type it then?  And yes, it can be created


I got a message about this from GHCi; I must have been to fast trying to  
implement this.


--
Regards,
Henk-Jan van Tuyl


--
http://functor.bamikanarie.com
http://Van.Tuyl.eu/
--


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


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 #-}
  import Control.Monad.Writer
 
 
  k :: (MonadWriter [Int] m) = m [Int]
 
  k = let f x = tell [x]  f (x + 1) in f 0
 
 
  works :: [Int]
  works = snd $ runWriter k
 
 
  hangs :: IO [Int]
  hangs = snd `liftM` runWriterT k  

runWriterT :: MonadWriter w m a = WriterT w m a - m (a, w)

which is to say runWriterT k :: IO (a, [Int])

It's not going to return anything until the IO action terminates, which is to 
say never.

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


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 Int from
0 up.  Aside from the extra printing, it has the same behavior as your
writer.

For the result of a WriterT to be lazy readable, you need both the
monoid to be lazy readable, and the transformed monad to be lazy,
which IO isn't.

  -- ryan

2008/12/31 Paolino paolo.verone...@gmail.com:
 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) = m [Int]

 k = let f x = tell [x]  f (x + 1) in f 0


 works :: [Int]
 works = snd $ runWriter k


 hangs :: IO [Int]
 hangs = snd `liftM` runWriterT k


 main = take 20 `liftM` hangs = print



 The main hangs both interpreted and compiled on ghc 6.10.1.

 The issue is not exposing with IO alone as

 main = print test  main

 is a working program.

 Thanks for explanations.


 paolino


 ___
 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] 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 do you know when to tie the knot and
attach the list back together?

This is a big problem with knot-tied datastructures in Haskell; it's
very difficult to *untie* the knot and find the ends of the string
again!

Another example:

 -- constant space no matter how many elements you access
 list_1 = repeat 1 :: [Int]

 -- blows up to infinite size even though it's just repeat (1 + 1)
 list_2 = map (+1) list_1

  --ryan

On Wed, Dec 31, 2008 at 5:07 AM, Martijn van Steenbergen
mart...@van.steenbergen.nl wrote:
 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 Value and
 all other values are the same. All this of course
 in a pure way, that is without using (M/T/TM)Vars
 or IORefs.

 The short answer is: yes, but the complete DList structure will need to be
 built anew (if nodes in the updated list are needed).

 The longer answer is: Because everything is pure, 'update' will need to
 create a new DLNode with the new value. But then you will also want to
 update the node's neighbours to point to the newly created DLNode, because
 if you don't then moving forward and then backward one position would make
 you end up at the old value again. But to update the neighbours' links to
 the new node you need to create new neighbour DLNodes, because everything is
 pure. And so on, until the whole list has been recreated.

 To not need to recreate the whole list you will need some kind of
 assignment, and this is exactly what vars/refs are for.

 Hope this helps,

 Martijn.
 ___
 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] 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 do not have the 'bottom' input such as:

foo [] = []
foo (x:xs) = x : (foo xs)

thank you,

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


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 proof? How about the functions do not have the 'bottom' input
 such as:

 foo [] = []
 foo (x:xs) = x : (foo xs)


Okay, I'm not sure what you mean by bottom.  You could either mean the base
case, or you could mean bottom -- non-terminating inputs -- as in domain
theory.

Let's say you wanted to see if foo is equivalent to id.

id x = x

We can do it without considering nontermination, by induction on the
structure of the argument:

  First, the *base case*: empty lists.
foo [] = []
id [] = []
  Just by looking at the definitions of each.

 Now the inductive case.  Assume that foo xs = id xs, and show that foo
(x:xs) = id (x:xs), for all x (but a fixed xs).

 foo (x:xs) = x : foo xs
  foo xs = id xs  by our  the induction hypothesis, so
  foo (x:xs) = x : id xs = x : xs
 And then just by the definition of id:
  id (x:xs) = x : xs

And we're done.

Now, maybe you meant bottom as in nontermination.  In this case, we have to
prove that they do the same thing when given _|_ also.  This requires a
deeper understanding of the semantics of the language, but can be done
here.

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.

See http://en.wikibooks.org/wiki/Haskell/Denotational_semantics for more
about _|_.

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


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

* Functions to sample subsets

For a quick tutorial, see my blog post at 
http://quantile95.com/2008/12/31/monte-carlo-poker-odds/

Happy New Year, everyone!


Patrick

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


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 interesting to look at foo == id for input 
(_|_:xs) and all other possible positions and combinations of positions 
for bottom? I wonder how many cases you need to take into consideration 
to have covered every possible situation.


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


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 and id are 
  exactly the same function.
 
 Would it in general also be interesting to look at foo == id for input 
 (_|_:xs) and all other possible positions and combinations of positions 
 for bottom? I wonder how many cases you need to take into consideration 
 to have covered every possible situation.

That case is already covered by the (x:xs) case.  The interesting,
potentially extra, case is an infinite list.

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


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 maybe just to
hard in the circular case I tried my hand on a non circular version
coming up with the following.
data DList a =
  DLNode {left::(DList a), value::a, right::(DList a)} |
  Leaf

update :: DList a - a - DList a
update n newValue = n' where
  n' = DLNode (linkleft n n') newValue (linkright n n')

linkleft, linkright :: DList a - DList a - DList a
linkleft Leaf _ = Leaf
linkleft old new = l' where
  l  = left old
  l' = case l of {~Leaf - l; _ - l{left = linkleft l l', right = new}}


linkright Leaf _ = Leaf
linkright old new = r' where
  r  = right old
  r' = case r of {~Leaf - r; _ - r{right = linkright r r', left = new}}

Not the most elegant solution but relatively straightforward.
And it does what it should if the list is terminated with Leaves on
the left and
right. One can also run it on an circular list but then it just
doesn't work like
it should (which isn't surprising):

*T let l = mkDList [1..5]
*T takeF 11 l
[1,2,3,4,5,1,2,3,4,5,1]
*T let l' = update l (-1)
*T takeF 11 l'
[-1,2,3,4,5,1,2,3,4,5,1]

So my problem is whether it possible to implement update in a way that
makes takeF 11 l' return [-1,2,3,4,5,-1,2,3,4,5,-1], and if it is possible I
would appreciate any pointers on how because I just can't figure it out.
But I'm already thankful for the answers so far, especially for the pointer
to map (+1) (repeat (1::Int)) since I really didn't expect it to behave like
that. And I would like to apologize for being too short in the formulation of
my original question.

cheers
Stephan

On Thu, Jan 1, 2009 at 8:11 AM, Ryan Ingram ryani.s...@gmail.com wrote:
 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 do you know when to tie the knot and
 attach the list back together?

 This is a big problem with knot-tied datastructures in Haskell; it's
 very difficult to *untie* the knot and find the ends of the string
 again!

 Another example:

 -- constant space no matter how many elements you access
 list_1 = repeat 1 :: [Int]

 -- blows up to infinite size even though it's just repeat (1 + 1)
 list_2 = map (+1) list_1

  --ryan

 On Wed, Dec 31, 2008 at 5:07 AM, Martijn van Steenbergen
 mart...@van.steenbergen.nl wrote:
 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 Value and
 all other values are the same. All this of course
 in a pure way, that is without using (M/T/TM)Vars
 or IORefs.

 The short answer is: yes, but the complete DList structure will need to be
 built anew (if nodes in the updated list are needed).

 The longer answer is: Because everything is pure, 'update' will need to
 create a new DLNode with the new value. But then you will also want to
 update the node's neighbours to point to the newly created DLNode, because
 if you don't then moving forward and then backward one position would make
 you end up at the old value again. But to update the neighbours' links to
 the new node you need to create new neighbour DLNodes, because everything is
 pure. And so on, until the whole list has been recreated.

 To not need to recreate the whole list you will need some kind of
 assignment, and this is exactly what vars/refs are for.

 Hope this helps,

 Martijn.
 ___
 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] 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 _|_ 
= _|_ ? and in the case of

 bad () = _|_   
 bad _|_ = ()


mean not every function with a _|_ input will issue a _|_ output, so we have to 
say what result will be issued by a _|_ input in the definitions of the 
functions if we want to prove the equvalence between them?

However, in the case of   map f _|_  , I do believe the result will be _|_ 
since it can not be anything else, but how I could prove this? any clue? 

ps, the definition of map does not mention anything about _|_ .

Thanks
Raeck


From: Luke Palmer 
Sent: Wednesday, December 31, 2008 10:43 PM
To: Max.cs ; ra...@msn.com 
Subject: Re: [Haskell-cafe] bottom case in proof by induction


On Wed, Dec 31, 2008 at 3:28 PM, Max.cs max.cs.2...@googlemail.com wrote:

  thanks Luke,

  so you mean the  _|_  is necessary only when I have defined the pattern  _|_  
such as

  foo [] = []
  foo  _|_  =  _|_ 
  foo (x:xs) = x( foo xs )
  -- consider non-termination case

That is illegal Haskell.  But another way of putting that is that whenever you 
do any pattern matching, eg.:

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:

halts () = True
halts _|_ = False

Because _|_ is the denotation of a program which never halts.

To do it a bit more domain-theoretically, I'll first cite the result that every 
function has a fixed point.  That is, for every f, there is a function fix f, 
where fix f = f (fix f). (The fix function is actually available in Haskell 
from the module Data.Function).  Then let's consider this bad function:

bad () = _|_-- you can't write _|_ in Haskell, but undefined or let x = 
x in x mean the same thing
bad _|_ = () 

Then what is fix f?  Well, it either terminates or it doesn't, right?  I.e. fix 
f = () or fix f = _|_.

Taking into account that fix f = f (fix f):
If it does:  fix f = () = f () = _|_, a contradiction.
If it doesn't: fix f = _|_ = f _|_ = (), another contradiction.

From a mathematical perspective, that's why you can't pattern match on _|_.

From an operational perspective, it's just that _|_ means never terminates, 
and we can't determine that, because we would try to run it until it doesn't 
terminate, which is meaningless...

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


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 proof, how I could say the right side must be _|_ without
 defining foo _|_ = _|_ ?

This definition is taken care of for you by the definition of Haskell
pattern matching.  If the first equation for a function has a pattern
other than

  * a variable or
  * a lazy pattern (~p)

for a given argument, then supplying _|_ for that argument /must/ (if
the application is total) return _|_.  By rule.  (We say the pattern is
strict, in this case).

  and in the case of
  
  bad () = _|_   
  bad _|_ = ()

Note that these equations (which are not in the right form for the
Haskell equations that define Hasekll functions) aren't satisfied by any
Haskell function!

 mean not every function with a _|_ input will issue a _|_ output,

True --- but we can say a couple of things:

  * For all Haskell functions f, if f _|_ is an application of a
constructor C, then f x is an application of C (to some value), for all
x.  [1]
  * For all Haskell functions f, if f _|_ is a lambda expression, then f
x is a lambda expression, for all x.

The only other possibility for f _|_ is _|_.

(Do you see why bad above is impossible?)

 so we have to say what result will be issued by a _|_ input in the
 definitions of the functions if we want to prove the equvalence
 between them?

You have to deduce what the value at _|_ will be.

 However, in the case of   map f _|_  , I do believe the result will be
 _|_ since it can not be anything else, but how I could prove this? any
 clue?

Appeal to the semantics of Haskell pattern matching.  If you like, you
can de-sugar the definition of map a little, to get

  map = \ f xn - case xn of
[] - []
x:xn0 - f x : map f xn0

And then you know that

case _|_ of
  [] - ...
  ...
  = _|_

whatever you fill in for the ellipses.  (Do you see why this *must* be
part of the language definition?)

 ps, the definition of map does not mention anything about _|_ .

The behavior of map f _|_ is fixed by the definition of Haskell pattern
matching.

jcc


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


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 proof, how I could say the right side must be _|_ without defining foo
 _|_ = _|_ ? and in the case of

Because _|_ is matched against a refutable pattern ([], in this case), so when 
foo is called with argument _|_, the runtime tries to match it against []. 
For that, it must reduce it far enough to know its top level constructor, 
which by definition of _|_ isn't possible, so the pattern match won't 
terminate, hence foo _|_ is a nonterminating computation, i.e. _|_.


  bad () = _|_
  bad _|_ = ()

You can't do that. You can only pattern-match against patterns, which _|_ 
isn't. 


 mean not every function with a _|_ input will issue a _|_ output, so we
 have to say what result will be issued by a _|_ input in the definitions of
 the functions if we want to prove the equvalence between them?

If you match against an irrefutable pattern (variable, wildcard or ~pattern), 
the matching succeeds without evaluating the argument, so then you can have 
functions which return a terminating value for nonterminating arguments:

lazyMap ~(x:xs) = [[],[x],xs]

*LazyTest lazyMap undefined
[[],[*** Exception: Prelude.undefined
*LazyTest lazyMap []
[[],[*** Exception: PrintPer.hs:28:0-28: Irrefutable pattern failed for 
pattern (x : xs)
*LazyTest take 1 $ lazyMap undefined
[[]]





 However, in the case of   map f _|_  , I do believe the result will be _|_
 since it can not be anything else, but how I could prove this? any clue?

 ps, the definition of map does not mention anything about _|_ .

As above, evaluation of map f _|_ tries to match _|_ against [], which doesn't 
terminate.


 Thanks
 Raeck


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


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
  would imply we could solve the halting problem:
   
  in a proof, how I could say the right side must be _|_ without
  defining foo _|_ = _|_ ?
 
 This definition is taken care of for you by the definition of Haskell
 pattern matching.  If the first equation for a function has a pattern
 other than
 
   * a variable or
   * a lazy pattern (~p)
 
 for a given argument, then supplying _|_ for that argument /must/ (if
 the application is total) return _|_.  By rule.  (We say the pattern is
 strict, in this case).
 
   and in the case of
   
   bad () = _|_   
   bad _|_ = ()
 
 Note that these equations (which are not in the right form for the
 Haskell equations that define Hasekll functions) aren't satisfied by any
 Haskell function!

This isn't just a quirk of Haskell semantics.  bad is not computable.
Period.

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


[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
HackageDB, recaptcha.

Upgrading from older versions of gitit:

The format of gitit's user database has changed. (gitit now generates a
new random salt for each user, instead of using a single static salt for
all users.) Unfortunately, this means that current users of gitit (yes,
all seven of you) will have to delete your gitit-users file and have
your users create new accounts.  Sorry about the breaking change, but
better now than later.

When you upgrade, you'll also need to delete the _local directory,
since changes have been made to the data structure that holds the
application state.  This shouldn't have any ill effects, since
everything of lasting importance (users, pages) is stored elsewhere.

If you use a configuration file, or if you want to start using reCAPTCHA
(which requires a configuration file), you will also have to add fields
for the captcha system. See data/SampleConfig.hs for the format.

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


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 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) = m [Int]
 
   k = let f x = tell [x]  f (x + 1) in f 0
 
 
   works :: [Int]
   works = snd $ runWriter k
 
 
   hangs :: IO [Int]
   hangs = snd `liftM` runWriterT k

 runWriterT :: MonadWriter w m a = WriterT w m a - m (a, w)

 which is to say runWriterT k :: IO (a, [Int])

 It's not going to return anything until the IO action terminates, which is
 to say never.


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


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 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 Int from
 0 up.  Aside from the extra printing, it has the same behavior as your
 writer.

 For the result of a WriterT to be lazy readable, you need both the
 monoid to be lazy readable, and the transformed monad to be lazy,
 which IO isn't.

  -- ryan

 2008/12/31 Paolino paolo.verone...@gmail.com:
  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) = m [Int]
 
  k = let f x = tell [x]  f (x + 1) in f 0
 
 
  works :: [Int]
  works = snd $ runWriter k
 
 
  hangs :: IO [Int]
  hangs = snd `liftM` runWriterT k
 
 
  main = take 20 `liftM` hangs = print
 
 
 
  The main hangs both interpreted and compiled on ghc 6.10.1.
 
  The issue is not exposing with IO alone as
 
  main = print test  main
 
  is a working program.
 
  Thanks for explanations.
 
 
  paolino
 
 
  ___
  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] 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

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


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 [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH


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


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 seems not accpetable in haskell ?

any way I could achieve this ?

Thanks

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




PGP.sig
Description: Signierter Teil der Nachricht
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe