[Haskell-cafe] HXT: Replace an element with its text

2012-06-26 Thread Michael Orlitzky
I would like to replace,

  bodya href=#foo/a/body

with,

  bodyfoo/body

using HXT. So far, the closest I've come is to parse the HTML and apply
the following stuff:

  is_link :: (ArrowXml a) = a XmlTree XmlTree
  is_link =
hasName a

  replace_links_with_their_text :: (ArrowXml a) = a XmlTree XmlTree
  replace_links_with_their_text =
processTopDown $ (getText  mkText) `when` is_link

Unfortunately, this just removes the a element and its text entirely.
The other-closest solution is,

  replace_links_with_their_text :: (ArrowXml a) = a XmlTree XmlTree
  replace_links_with_their_text =
processTopDown $ (txt foo) `when` is_link

Of course, I don't want to hard-code the value foo, and I can't figure
out a way to feed the element's text back into 'txt'.

Anyone tried this before?

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


Re: [Haskell-cafe] Unambiguous choice implementation

2012-06-26 Thread Heinrich Apfelmus

Bartosz Milewski wrote:

Thanks, Heinrich. I looked at the examples and at the references you
provided. I understand the semantic model, so I guess I'm mostly trying to
understand the implementation.


Ok. As I mentioned, if you just want to use the library there is no need 
to understand the implementation.



Conal's paper was mostly about refining data
structures in order to provide better implementation. It's all beautiful up
to the point where he introduces the unamb hack. How did you manage to work
around this problem and implement event merging efficiently?


Essentially, Conal implements events as

type Event a = [(Time,a)]

The trouble is that when merging events, this representation forces you 
to wait for both events. In other words, the pattern match


union ((t1,x1):e1) ((t2,x2):e2) = ...

needs to know the times of occurrences of both events before it can 
return the earlier one. The trouble is that the  merge  function should 
have returned the earlier one right away, before knowing exactly when 
the later one happens. The purpose of the  unamb  hack is circumvent 
that problem.



Reactive-banana's very simple solution to this problem is to represent 
events as


type Event a = [(Time, Maybe a)]

and impose the additional invariant that all events in your program are 
synchronized, in the sense that they indicate their occurrences at the 
same times^1. If they don't occur at that time, they use  Nothing . 
Then, you can implement  merge  simply as


union ((t1,x1):e1) ((t2,x2):e2) = -- we always have  t1 = t2
(t1, combine x1 x2) : union e1 e2
where
combine (Just x) Nothing  = Just x   -- only left occurs
combine Nothing  (Just y) = Just y   -- only right occurs
combine (Just x) (Just y) = Just x   -- simultaneous occurrence
combine Nothing  Nothing  = Nothing  -- neither occurs

Since the times are given globally, we can also remove them and obtain

type Event a = [Maybe a]

This is how  Reactive.Banana.Model  does it.


Of course, keeping track of a lot of  Nothing  is something that can be 
optimized. The optimization to apply here is to transform the 
implementation into a push-driven style. I haven't published the details 
yet, but some design notes can be found here.


http://apfelmus.nfshost.com/blog/2011/04/24-frp-push-driven-sharing.html


^1: Note that the times do not need to follow a uniform time step.


Best regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com


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


Re: [Haskell-cafe] HXT: Replace an element with its text

2012-06-26 Thread Ivan Perez
Hi,
 You code fails because a link is not a node of kind Text, I think.
What you want is to get the text from a child node of an anchor node.
I think the following should work:

is_link :: (ArrowXml a) = a XmlTree XmlTree
is_link = hasName a

process_link :: (ArrowXml a) = a XmlTree XmlTree
process_link = getChildren  getText  mkText

replace_links_with_their_text :: (ArrowXml a) = a XmlTree XmlTree
replace_links_with_their_text =
  processTopDown $ process_link `when` is_link

Cheers,
Ivan.

On 26 June 2012 06:58, Michael Orlitzky mich...@orlitzky.com wrote:
 I would like to replace,

   bodya href=#foo/a/body

 with,

   bodyfoo/body

 using HXT. So far, the closest I've come is to parse the HTML and apply
 the following stuff:

   is_link :: (ArrowXml a) = a XmlTree XmlTree
   is_link =
 hasName a

   replace_links_with_their_text :: (ArrowXml a) = a XmlTree XmlTree
   replace_links_with_their_text =
 processTopDown $ (getText  mkText) `when` is_link

 Unfortunately, this just removes the a element and its text entirely.
 The other-closest solution is,

   replace_links_with_their_text :: (ArrowXml a) = a XmlTree XmlTree
   replace_links_with_their_text =
 processTopDown $ (txt foo) `when` is_link

 Of course, I don't want to hard-code the value foo, and I can't figure
 out a way to feed the element's text back into 'txt'.

 Anyone tried this before?

 ___
 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] HXT: Replace an element with its text

2012-06-26 Thread Ivan Perez
(And just to be as precise as I can and avoid confusion, when I said
link I meant unnamed anchor node with an href attribute)

On 26 June 2012 10:15, Ivan Perez ivanperezdoming...@gmail.com wrote:
 Hi,
  You code fails because a link is not a node of kind Text, I think.
 What you want is to get the text from a child node of an anchor node.
 I think the following should work:

 is_link :: (ArrowXml a) = a XmlTree XmlTree
 is_link = hasName a

 process_link :: (ArrowXml a) = a XmlTree XmlTree
 process_link = getChildren  getText  mkText

 replace_links_with_their_text :: (ArrowXml a) = a XmlTree XmlTree
 replace_links_with_their_text =
   processTopDown $ process_link `when` is_link

 Cheers,
 Ivan.

 On 26 June 2012 06:58, Michael Orlitzky mich...@orlitzky.com wrote:
 I would like to replace,

   bodya href=#foo/a/body

 with,

   bodyfoo/body

 using HXT. So far, the closest I've come is to parse the HTML and apply
 the following stuff:

   is_link :: (ArrowXml a) = a XmlTree XmlTree
   is_link =
 hasName a

   replace_links_with_their_text :: (ArrowXml a) = a XmlTree XmlTree
   replace_links_with_their_text =
 processTopDown $ (getText  mkText) `when` is_link

 Unfortunately, this just removes the a element and its text entirely.
 The other-closest solution is,

   replace_links_with_their_text :: (ArrowXml a) = a XmlTree XmlTree
   replace_links_with_their_text =
 processTopDown $ (txt foo) `when` is_link

 Of course, I don't want to hard-code the value foo, and I can't figure
 out a way to feed the element's text back into 'txt'.

 Anyone tried this before?

 ___
 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] StableNames and monadic functions

2012-06-26 Thread Ismael Figueroa Palet
I'm using StableNames to have a notion of function equality, and I'm
running into problems when using monadic functions.

Consider the code below, file Test.hs

import System.Mem.StableName
import Control.Monad.State

eq :: a - b - IO Bool
eq a b = do
 pa - makeStableName a
 pb - makeStableName b
 return (hashStableName pa == hashStableName pb)

successor :: (Num a, Monad m) = a - m a
successor n = return (n+1)

main :: IO ()
main = do
   b1 - eq (successor :: Int - Maybe Int) (successor :: Int - Maybe
Int)
   b2 - eq (successor :: Int - State Int Int) (successor :: Int -
State Int Int)
   print (show b1 ++   ++ show b2)

Running the code into ghci the result is False False. There is some old
post saying that this is due to the dictionary-passing style for
typeclasses, and compiling with optimizations improves the situation.

Compiling with ghc --make -O Tests.hs and running the program, the result
is True True, which is what I expect.
However, if I change main to be like the following:

main :: IO ()
main = do
   b2 - eq (successor :: Int - State Int Int) (successor :: Int -
State Int Int)
   b1 - eq (successor :: Int - Maybe Int) (successor :: Int - Maybe
Int)
   print (show b1 ++   ++ show b2)

i.e. just changing the sequential order, and then compiling again with the
same command, I get True False, which is very confusing for me.
Similar situations happens when using the state monad transformer, and
manually built variations of it.

It sounds the problem is with hidden closures created somewhere that do not
point to the same memory locations, so StableNames yields false for that
cases, but it is not clear to me under what circumstances this situation
happens. Is there other way to get some approximation of function equality?
or a way to configure the behavior of StableNames in presence of class
constraints?

I'm using the latests Haskell Platform on OS X Lion, btw.

Thanks

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


Re: [Haskell-cafe] StableNames and monadic functions

2012-06-26 Thread Ismael Figueroa Palet
Thanks Lorenzo, I'm cc'ing the list with your response also:

As you point out, when you do some kind of let-binding, using the where
clause, or explicit let as in:

main :: IO ()
main = do
   let f1 = (successor :: Int - State Int Int)
   let f2 = (successor :: Int - Maybe Int)
   b2 - eq f2 f2
   b1 - eq f1 f1
   print (show b1 ++   ++ show b2)

The behavior is as expected. I guess the binding triggers some internal
optimization or gives more information to the type checker; but I'm still
not clear why it is required to be done this way -- having to let-bind
every function is kind of awkward.

I know the details of StableNames are probably implementation-dependent,
but I'm still wondering about how to detect / restrict this situation.

Thanks


2012/6/26 Lorenzo Bolla lbo...@gmail.com

 From StableName docs:

 The reverse is not necessarily true: if two stable names are not equal,
 then the objects they name may still be equal.


 This version works as expected:

 import System.Mem.StableName
 import Control.Monad.State

 eq :: a - b - IO Bool
 eq a b = do
  pa - makeStableName a
  pb - makeStableName b
  return (hashStableName pa == hashStableName pb)

 successor :: (Num a, Monad m) = a - m a
 successor n = return (n+1)

 --  main :: IO ()
 --  main = do
 -- b2 - eq (successor :: Int - State Int Int) (successor :: Int
 - State Int Int)
 -- b1 - eq (successor :: Int - Maybe Int) (successor :: Int -
 Maybe Int)
 -- print (show b1 ++   ++ show b2)

 main :: IO ()
 main = do
b2 - eq f2 f2
b1 - eq f1 f1
print (show b1 ++   ++ show b2)
where f1 = (successor :: Int - Maybe Int)
  f2 = (successor :: Int - State Int Int)



 hth,
 L.




 On Tue, Jun 26, 2012 at 1:15 PM, Ismael Figueroa Palet 
 ifiguer...@gmail.com wrote:

 I'm using StableNames to have a notion of function equality, and I'm
 running into problems when using monadic functions.

 Consider the code below, file Test.hs

 import System.Mem.StableName
 import Control.Monad.State

 eq :: a - b - IO Bool
 eq a b = do
  pa - makeStableName a
  pb - makeStableName b
  return (hashStableName pa == hashStableName pb)

 successor :: (Num a, Monad m) = a - m a
 successor n = return (n+1)

 main :: IO ()
 main = do
b1 - eq (successor :: Int - Maybe Int) (successor :: Int -
 Maybe Int)
b2 - eq (successor :: Int - State Int Int) (successor :: Int -
 State Int Int)
print (show b1 ++   ++ show b2)

 Running the code into ghci the result is False False. There is some old
 post saying that this is due to the dictionary-passing style for
 typeclasses, and compiling with optimizations improves the situation.

 Compiling with ghc --make -O Tests.hs and running the program, the result
 is True True, which is what I expect.
 However, if I change main to be like the following:

  main :: IO ()
 main = do
b2 - eq (successor :: Int - State Int Int) (successor :: Int -
 State Int Int)
b1 - eq (successor :: Int - Maybe Int) (successor :: Int -
 Maybe Int)
print (show b1 ++   ++ show b2)

 i.e. just changing the sequential order, and then compiling again with
 the same command, I get True False, which is very confusing for me.
 Similar situations happens when using the state monad transformer, and
 manually built variations of it.

 It sounds the problem is with hidden closures created somewhere that do
 not point to the same memory locations, so StableNames yields false for
 that cases, but it is not clear to me under what circumstances this
 situation happens. Is there other way to get some approximation of function
 equality? or a way to configure the behavior of StableNames in presence
 of class constraints?

 I'm using the latests Haskell Platform on OS X Lion, btw.

 Thanks

 --
 Ismael


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





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


Re: [Haskell-cafe] StableNames and monadic functions

2012-06-26 Thread Lorenzo Bolla
The point I was making is that StableName might be what you want. You are
using it to check if two functions are the same by comparing their
stablehash. But from StableName documentation:

The reverse is not necessarily true: if two stable names are not equal,
 then the objects they name may still be equal.


The `eq` you implemented means this, I reckon: if `eq` returns True then
the 2 functions are equal, if `eq` returns False then you can't tell!

Does it make sense?
L.


On Tue, Jun 26, 2012 at 1:54 PM, Ismael Figueroa Palet ifiguer...@gmail.com
 wrote:

 Thanks Lorenzo, I'm cc'ing the list with your response also:

 As you point out, when you do some kind of let-binding, using the where
 clause, or explicit let as in:

 main :: IO ()
 main = do
let f1 = (successor :: Int - State Int Int)
let f2 = (successor :: Int - Maybe Int)
b2 - eq f2 f2
b1 - eq f1 f1
print (show b1 ++   ++ show b2)

 The behavior is as expected. I guess the binding triggers some internal
 optimization or gives more information to the type checker; but I'm still
 not clear why it is required to be done this way -- having to let-bind
 every function is kind of awkward.

 I know the details of StableNames are probably implementation-dependent,
 but I'm still wondering about how to detect / restrict this situation.

 Thanks


 2012/6/26 Lorenzo Bolla lbo...@gmail.com

 From StableName docs:

 The reverse is not necessarily true: if two stable names are not equal,
 then the objects they name may still be equal.


 This version works as expected:

 import System.Mem.StableName
 import Control.Monad.State

 eq :: a - b - IO Bool
 eq a b = do
  pa - makeStableName a
  pb - makeStableName b
  return (hashStableName pa == hashStableName pb)

 successor :: (Num a, Monad m) = a - m a
 successor n = return (n+1)

 --  main :: IO ()
 --  main = do
 -- b2 - eq (successor :: Int - State Int Int) (successor :: Int
 - State Int Int)
 -- b1 - eq (successor :: Int - Maybe Int) (successor :: Int -
 Maybe Int)
 -- print (show b1 ++   ++ show b2)

 main :: IO ()
 main = do
b2 - eq f2 f2
b1 - eq f1 f1
print (show b1 ++   ++ show b2)
where f1 = (successor :: Int - Maybe Int)
  f2 = (successor :: Int - State Int Int)



 hth,
 L.




 On Tue, Jun 26, 2012 at 1:15 PM, Ismael Figueroa Palet 
 ifiguer...@gmail.com wrote:

 I'm using StableNames to have a notion of function equality, and I'm
 running into problems when using monadic functions.

 Consider the code below, file Test.hs

 import System.Mem.StableName
 import Control.Monad.State

 eq :: a - b - IO Bool
 eq a b = do
  pa - makeStableName a
  pb - makeStableName b
  return (hashStableName pa == hashStableName pb)

 successor :: (Num a, Monad m) = a - m a
 successor n = return (n+1)

 main :: IO ()
 main = do
b1 - eq (successor :: Int - Maybe Int) (successor :: Int -
 Maybe Int)
b2 - eq (successor :: Int - State Int Int) (successor :: Int -
 State Int Int)
print (show b1 ++   ++ show b2)

 Running the code into ghci the result is False False. There is some
 old post saying that this is due to the dictionary-passing style for
 typeclasses, and compiling with optimizations improves the situation.

 Compiling with ghc --make -O Tests.hs and running the program, the
 result is True True, which is what I expect.
 However, if I change main to be like the following:

  main :: IO ()
 main = do
b2 - eq (successor :: Int - State Int Int) (successor :: Int -
 State Int Int)
b1 - eq (successor :: Int - Maybe Int) (successor :: Int -
 Maybe Int)
print (show b1 ++   ++ show b2)

 i.e. just changing the sequential order, and then compiling again with
 the same command, I get True False, which is very confusing for me.
 Similar situations happens when using the state monad transformer, and
 manually built variations of it.

 It sounds the problem is with hidden closures created somewhere that do
 not point to the same memory locations, so StableNames yields false for
 that cases, but it is not clear to me under what circumstances this
 situation happens. Is there other way to get some approximation of function
 equality? or a way to configure the behavior of StableNames in presence
 of class constraints?

 I'm using the latests Haskell Platform on OS X Lion, btw.

 Thanks

 --
 Ismael


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





 --
 Ismael


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


Re: [Haskell-cafe] StableNames and monadic functions

2012-06-26 Thread Ismael Figueroa Palet
2012/6/26 Lorenzo Bolla lbo...@gmail.com

 The point I was making is that StableName might be what you want. You are
 using it to check if two functions are the same by comparing their
 stablehash. But from StableName documentation:

 The reverse is not necessarily true: if two stable names are not equal,
 then the objects they name may still be equal.


 The `eq` you implemented means this, I reckon: if `eq` returns True then
 the 2 functions are equal, if `eq` returns False then you can't tell!

 Does it make sense?
 L.


Yes  it does make sense, and I'm wondering why the hash are equal in one
case but are not equal on the other case (i.e. using let/where vs not using
it) because I'd like it to behave the same in both situations

Thanks again




 On Tue, Jun 26, 2012 at 1:54 PM, Ismael Figueroa Palet 
 ifiguer...@gmail.com wrote:

 Thanks Lorenzo, I'm cc'ing the list with your response also:

 As you point out, when you do some kind of let-binding, using the where
 clause, or explicit let as in:

 main :: IO ()
 main = do
let f1 = (successor :: Int - State Int Int)
let f2 = (successor :: Int - Maybe Int)
b2 - eq f2 f2
b1 - eq f1 f1
print (show b1 ++   ++ show b2)

 The behavior is as expected. I guess the binding triggers some internal
 optimization or gives more information to the type checker; but I'm still
 not clear why it is required to be done this way -- having to let-bind
 every function is kind of awkward.

 I know the details of StableNames are probably implementation-dependent,
 but I'm still wondering about how to detect / restrict this situation.

 Thanks


 2012/6/26 Lorenzo Bolla lbo...@gmail.com

 From StableName docs:

 The reverse is not necessarily true: if two stable names are not equal,
 then the objects they name may still be equal.


 This version works as expected:

 import System.Mem.StableName
 import Control.Monad.State

 eq :: a - b - IO Bool
 eq a b = do
  pa - makeStableName a
  pb - makeStableName b
  return (hashStableName pa == hashStableName pb)

 successor :: (Num a, Monad m) = a - m a
 successor n = return (n+1)

 --  main :: IO ()
 --  main = do
 -- b2 - eq (successor :: Int - State Int Int) (successor ::
 Int - State Int Int)
 -- b1 - eq (successor :: Int - Maybe Int) (successor :: Int -
 Maybe Int)
 -- print (show b1 ++   ++ show b2)

 main :: IO ()
 main = do
b2 - eq f2 f2
b1 - eq f1 f1
print (show b1 ++   ++ show b2)
where f1 = (successor :: Int - Maybe Int)
  f2 = (successor :: Int - State Int Int)



 hth,
 L.




 On Tue, Jun 26, 2012 at 1:15 PM, Ismael Figueroa Palet 
 ifiguer...@gmail.com wrote:

 I'm using StableNames to have a notion of function equality, and I'm
 running into problems when using monadic functions.

 Consider the code below, file Test.hs

 import System.Mem.StableName
 import Control.Monad.State

 eq :: a - b - IO Bool
 eq a b = do
  pa - makeStableName a
  pb - makeStableName b
  return (hashStableName pa == hashStableName pb)

 successor :: (Num a, Monad m) = a - m a
 successor n = return (n+1)

 main :: IO ()
 main = do
b1 - eq (successor :: Int - Maybe Int) (successor :: Int -
 Maybe Int)
b2 - eq (successor :: Int - State Int Int) (successor :: Int
 - State Int Int)
print (show b1 ++   ++ show b2)

 Running the code into ghci the result is False False. There is some
 old post saying that this is due to the dictionary-passing style for
 typeclasses, and compiling with optimizations improves the situation.

 Compiling with ghc --make -O Tests.hs and running the program, the
 result is True True, which is what I expect.
 However, if I change main to be like the following:

  main :: IO ()
 main = do
b2 - eq (successor :: Int - State Int Int) (successor :: Int
 - State Int Int)
b1 - eq (successor :: Int - Maybe Int) (successor :: Int -
 Maybe Int)
print (show b1 ++   ++ show b2)

 i.e. just changing the sequential order, and then compiling again with
 the same command, I get True False, which is very confusing for me.
 Similar situations happens when using the state monad transformer, and
 manually built variations of it.

 It sounds the problem is with hidden closures created somewhere that do
 not point to the same memory locations, so StableNames yields false for
 that cases, but it is not clear to me under what circumstances this
 situation happens. Is there other way to get some approximation of function
 equality? or a way to configure the behavior of StableNames in presence
 of class constraints?

 I'm using the latests Haskell Platform on OS X Lion, btw.

 Thanks

 --
 Ismael


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





 --
 Ismael





-- 
Ismael
___

Re: [Haskell-cafe] HXT: Replace an element with its text

2012-06-26 Thread Uwe Schmidt
Michael Orlitzky wrote

 I would like to replace,

   bodya href=#foo/a/body

 with,

   bodyfoo/body

 using HXT. So far, the closest I've come is to parse the HTML and apply
 the following stuff:

   is_link :: (ArrowXml a) = a XmlTree XmlTree
   is_link =
 hasName a

   replace_links_with_their_text :: (ArrowXml a) = a XmlTree XmlTree
   replace_links_with_their_text =
 processTopDown $ (getText  mkText) `when` is_link

processTopDown $ (deep getText  mkText) `when` is_link

should do it. The deep getText will find all Text nodes, independent
of the nesting of elements in the a.../a element. If you then
write the result into a document every thing is fine.

One small problem can occur when the content of the a Element
has e.g. the form

bodya href=#foobbar/b/a/body

The resulting DOM then still contains two text nodes, one for foo
and one for bar. If you later search for a text foobar
you don't find a node. The melting of adjacent text nodes can
be done with

... (xshow (deep getText)  mkText) ...

Cheers,

  Uwe

-- 

Uwe Schmidt
FH Wedel
Web: http://www.fh-wedel.de/~si/


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


Re: [Haskell-cafe] StableNames and monadic functions

2012-06-26 Thread Lorenzo Bolla
I think about StableName like the  operator in C, that returns you the
memory address of a variable. It's not the same for many reasons, but by
analogy, if x == y then x == y, but x != y does not imply x != y.

So, values that are semantically equal, may be stored in different memory
locations and have different StableNames.

The fact that changing the order of the lines also changes the result of
the computation is obviously stated in the type signature of
makeStableName, which lives in the IO monad. On the other hand
hashStableNAme is a pure function.

L.



On Tue, Jun 26, 2012 at 3:26 PM, Ismael Figueroa Palet ifiguer...@gmail.com
 wrote:



 2012/6/26 Lorenzo Bolla lbo...@gmail.com

 The point I was making is that StableName might be what you want. You are
 using it to check if two functions are the same by comparing their
 stablehash. But from StableName documentation:

  The reverse is not necessarily true: if two stable names are not equal,
 then the objects they name may still be equal.


 The `eq` you implemented means this, I reckon: if `eq` returns True then
 the 2 functions are equal, if `eq` returns False then you can't tell!

 Does it make sense?
 L.


 Yes  it does make sense, and I'm wondering why the hash are equal in one
 case but are not equal on the other case (i.e. using let/where vs not using
 it) because I'd like it to behave the same in both situations

 Thanks again




 On Tue, Jun 26, 2012 at 1:54 PM, Ismael Figueroa Palet 
 ifiguer...@gmail.com wrote:

 Thanks Lorenzo, I'm cc'ing the list with your response also:

 As you point out, when you do some kind of let-binding, using the
 where clause, or explicit let as in:

 main :: IO ()
 main = do
let f1 = (successor :: Int - State Int Int)
let f2 = (successor :: Int - Maybe Int)
b2 - eq f2 f2
b1 - eq f1 f1
print (show b1 ++   ++ show b2)

 The behavior is as expected. I guess the binding triggers some internal
 optimization or gives more information to the type checker; but I'm still
 not clear why it is required to be done this way -- having to let-bind
 every function is kind of awkward.

 I know the details of StableNames are probably implementation-dependent,
 but I'm still wondering about how to detect / restrict this situation.

 Thanks


 2012/6/26 Lorenzo Bolla lbo...@gmail.com

 From StableName docs:

 The reverse is not necessarily true: if two stable names are not
 equal, then the objects they name may still be equal.


 This version works as expected:

 import System.Mem.StableName
 import Control.Monad.State

 eq :: a - b - IO Bool
 eq a b = do
  pa - makeStableName a
  pb - makeStableName b
  return (hashStableName pa == hashStableName pb)

 successor :: (Num a, Monad m) = a - m a
 successor n = return (n+1)

 --  main :: IO ()
 --  main = do
 -- b2 - eq (successor :: Int - State Int Int) (successor ::
 Int - State Int Int)
 -- b1 - eq (successor :: Int - Maybe Int) (successor :: Int
 - Maybe Int)
 -- print (show b1 ++   ++ show b2)

 main :: IO ()
 main = do
b2 - eq f2 f2
b1 - eq f1 f1
print (show b1 ++   ++ show b2)
where f1 = (successor :: Int - Maybe Int)
  f2 = (successor :: Int - State Int Int)



 hth,
 L.




 On Tue, Jun 26, 2012 at 1:15 PM, Ismael Figueroa Palet 
 ifiguer...@gmail.com wrote:

 I'm using StableNames to have a notion of function equality, and I'm
 running into problems when using monadic functions.

 Consider the code below, file Test.hs

 import System.Mem.StableName
 import Control.Monad.State

 eq :: a - b - IO Bool
 eq a b = do
  pa - makeStableName a
  pb - makeStableName b
  return (hashStableName pa == hashStableName pb)

 successor :: (Num a, Monad m) = a - m a
 successor n = return (n+1)

 main :: IO ()
 main = do
b1 - eq (successor :: Int - Maybe Int) (successor :: Int -
 Maybe Int)
b2 - eq (successor :: Int - State Int Int) (successor :: Int
 - State Int Int)
print (show b1 ++   ++ show b2)

 Running the code into ghci the result is False False. There is some
 old post saying that this is due to the dictionary-passing style for
 typeclasses, and compiling with optimizations improves the situation.

 Compiling with ghc --make -O Tests.hs and running the program, the
 result is True True, which is what I expect.
 However, if I change main to be like the following:

  main :: IO ()
 main = do
b2 - eq (successor :: Int - State Int Int) (successor :: Int
 - State Int Int)
b1 - eq (successor :: Int - Maybe Int) (successor :: Int -
 Maybe Int)
print (show b1 ++   ++ show b2)

 i.e. just changing the sequential order, and then compiling again with
 the same command, I get True False, which is very confusing for me.
 Similar situations happens when using the state monad transformer, and
 manually built variations of it.

 It sounds the problem is with hidden closures 

Re: [Haskell-cafe] StableNames and monadic functions

2012-06-26 Thread Lorenzo Bolla
In other words there is a difference between Identity and Equivalence. What
you have implemented with StableName is an Identity (sometimes called
reference equality), as opposed to an Equivalence (aka value
equality).

In Python, for example:

 x = {1:2}
 y = {1:2}
 x == y
True
 x is y
False

L.


On Tue, Jun 26, 2012 at 3:42 PM, Lorenzo Bolla lbo...@gmail.com wrote:

 I think about StableName like the  operator in C, that returns you the
 memory address of a variable. It's not the same for many reasons, but by
 analogy, if x == y then x == y, but x != y does not imply x != y.

 So, values that are semantically equal, may be stored in different memory
 locations and have different StableNames.

 The fact that changing the order of the lines also changes the result of
 the computation is obviously stated in the type signature of
 makeStableName, which lives in the IO monad. On the other hand
 hashStableNAme is a pure function.

 L.



 On Tue, Jun 26, 2012 at 3:26 PM, Ismael Figueroa Palet 
 ifiguer...@gmail.com wrote:



 2012/6/26 Lorenzo Bolla lbo...@gmail.com

 The point I was making is that StableName might be what you want. You
 are using it to check if two functions are the same by comparing their
 stablehash. But from StableName documentation:

  The reverse is not necessarily true: if two stable names are not equal,
 then the objects they name may still be equal.


 The `eq` you implemented means this, I reckon: if `eq` returns True then
 the 2 functions are equal, if `eq` returns False then you can't tell!

 Does it make sense?
 L.


 Yes  it does make sense, and I'm wondering why the hash are equal in one
 case but are not equal on the other case (i.e. using let/where vs not using
 it) because I'd like it to behave the same in both situations

 Thanks again




 On Tue, Jun 26, 2012 at 1:54 PM, Ismael Figueroa Palet 
 ifiguer...@gmail.com wrote:

 Thanks Lorenzo, I'm cc'ing the list with your response also:

 As you point out, when you do some kind of let-binding, using the
 where clause, or explicit let as in:

 main :: IO ()
 main = do
let f1 = (successor :: Int - State Int Int)
let f2 = (successor :: Int - Maybe Int)
b2 - eq f2 f2
b1 - eq f1 f1
print (show b1 ++   ++ show b2)

 The behavior is as expected. I guess the binding triggers some internal
 optimization or gives more information to the type checker; but I'm still
 not clear why it is required to be done this way -- having to let-bind
 every function is kind of awkward.

 I know the details of StableNames are probably
 implementation-dependent, but I'm still wondering about how to detect /
 restrict this situation.

 Thanks


 2012/6/26 Lorenzo Bolla lbo...@gmail.com

 From StableName docs:

 The reverse is not necessarily true: if two stable names are not
 equal, then the objects they name may still be equal.


 This version works as expected:

 import System.Mem.StableName
 import Control.Monad.State

 eq :: a - b - IO Bool
 eq a b = do
  pa - makeStableName a
  pb - makeStableName b
  return (hashStableName pa == hashStableName pb)

 successor :: (Num a, Monad m) = a - m a
 successor n = return (n+1)

 --  main :: IO ()
 --  main = do
 -- b2 - eq (successor :: Int - State Int Int) (successor ::
 Int - State Int Int)
 -- b1 - eq (successor :: Int - Maybe Int) (successor :: Int
 - Maybe Int)
 -- print (show b1 ++   ++ show b2)

 main :: IO ()
 main = do
b2 - eq f2 f2
b1 - eq f1 f1
print (show b1 ++   ++ show b2)
where f1 = (successor :: Int - Maybe Int)
  f2 = (successor :: Int - State Int Int)



 hth,
 L.




 On Tue, Jun 26, 2012 at 1:15 PM, Ismael Figueroa Palet 
 ifiguer...@gmail.com wrote:

 I'm using StableNames to have a notion of function equality, and I'm
 running into problems when using monadic functions.

 Consider the code below, file Test.hs

 import System.Mem.StableName
 import Control.Monad.State

 eq :: a - b - IO Bool
 eq a b = do
  pa - makeStableName a
  pb - makeStableName b
  return (hashStableName pa == hashStableName pb)

 successor :: (Num a, Monad m) = a - m a
 successor n = return (n+1)

 main :: IO ()
 main = do
b1 - eq (successor :: Int - Maybe Int) (successor :: Int -
 Maybe Int)
b2 - eq (successor :: Int - State Int Int) (successor :: Int
 - State Int Int)
print (show b1 ++   ++ show b2)

 Running the code into ghci the result is False False. There is some
 old post saying that this is due to the dictionary-passing style for
 typeclasses, and compiling with optimizations improves the situation.

 Compiling with ghc --make -O Tests.hs and running the program, the
 result is True True, which is what I expect.
 However, if I change main to be like the following:

  main :: IO ()
 main = do
b2 - eq (successor :: Int - State Int Int) (successor :: Int
 - State Int Int)
b1 - eq (successor :: Int - 

Re: [Haskell-cafe] StableNames and monadic functions

2012-06-26 Thread Ismael Figueroa Palet
thanks again for your comments, any idea on how to implement Equivalence
for functions?

2012/6/26 Lorenzo Bolla lbo...@gmail.com

 In other words there is a difference between Identity and Equivalence.
 What you have implemented with StableName is an Identity (sometimes
 called reference equality), as opposed to an Equivalence (aka value
 equality).

 In Python, for example:

  x = {1:2}
  y = {1:2}
  x == y
 True
  x is y
 False

 L.


 On Tue, Jun 26, 2012 at 3:42 PM, Lorenzo Bolla lbo...@gmail.com wrote:

 I think about StableName like the  operator in C, that returns you the
 memory address of a variable. It's not the same for many reasons, but by
 analogy, if x == y then x == y, but x != y does not imply x != y.

 So, values that are semantically equal, may be stored in different memory
 locations and have different StableNames.

 The fact that changing the order of the lines also changes the result of
 the computation is obviously stated in the type signature of
 makeStableName, which lives in the IO monad. On the other hand
 hashStableNAme is a pure function.

 L.



 On Tue, Jun 26, 2012 at 3:26 PM, Ismael Figueroa Palet 
 ifiguer...@gmail.com wrote:



 2012/6/26 Lorenzo Bolla lbo...@gmail.com

 The point I was making is that StableName might be what you want. You
 are using it to check if two functions are the same by comparing their
 stablehash. But from StableName documentation:

  The reverse is not necessarily true: if two stable names are not
 equal, then the objects they name may still be equal.


 The `eq` you implemented means this, I reckon: if `eq` returns True
 then the 2 functions are equal, if `eq` returns False then you can't tell!

 Does it make sense?
 L.


 Yes  it does make sense, and I'm wondering why the hash are equal in one
 case but are not equal on the other case (i.e. using let/where vs not using
 it) because I'd like it to behave the same in both situations

 Thanks again




 On Tue, Jun 26, 2012 at 1:54 PM, Ismael Figueroa Palet 
 ifiguer...@gmail.com wrote:

 Thanks Lorenzo, I'm cc'ing the list with your response also:

 As you point out, when you do some kind of let-binding, using the
 where clause, or explicit let as in:

 main :: IO ()
 main = do
let f1 = (successor :: Int - State Int Int)
let f2 = (successor :: Int - Maybe Int)
b2 - eq f2 f2
b1 - eq f1 f1
print (show b1 ++   ++ show b2)

 The behavior is as expected. I guess the binding triggers some
 internal optimization or gives more information to the type checker; but
 I'm still not clear why it is required to be done this way -- having to
 let-bind every function is kind of awkward.

 I know the details of StableNames are probably
 implementation-dependent, but I'm still wondering about how to detect /
 restrict this situation.

 Thanks


 2012/6/26 Lorenzo Bolla lbo...@gmail.com

 From StableName docs:

 The reverse is not necessarily true: if two stable names are not
 equal, then the objects they name may still be equal.


 This version works as expected:

 import System.Mem.StableName
 import Control.Monad.State

 eq :: a - b - IO Bool
 eq a b = do
  pa - makeStableName a
  pb - makeStableName b
  return (hashStableName pa == hashStableName pb)

 successor :: (Num a, Monad m) = a - m a
 successor n = return (n+1)

 --  main :: IO ()
 --  main = do
 -- b2 - eq (successor :: Int - State Int Int) (successor ::
 Int - State Int Int)
 -- b1 - eq (successor :: Int - Maybe Int) (successor :: Int
 - Maybe Int)
 -- print (show b1 ++   ++ show b2)

 main :: IO ()
 main = do
b2 - eq f2 f2
b1 - eq f1 f1
print (show b1 ++   ++ show b2)
where f1 = (successor :: Int - Maybe Int)
  f2 = (successor :: Int - State Int Int)



 hth,
 L.




 On Tue, Jun 26, 2012 at 1:15 PM, Ismael Figueroa Palet 
 ifiguer...@gmail.com wrote:

 I'm using StableNames to have a notion of function equality, and I'm
 running into problems when using monadic functions.

 Consider the code below, file Test.hs

 import System.Mem.StableName
 import Control.Monad.State

 eq :: a - b - IO Bool
 eq a b = do
  pa - makeStableName a
  pb - makeStableName b
  return (hashStableName pa == hashStableName pb)

 successor :: (Num a, Monad m) = a - m a
 successor n = return (n+1)

 main :: IO ()
 main = do
b1 - eq (successor :: Int - Maybe Int) (successor :: Int -
 Maybe Int)
b2 - eq (successor :: Int - State Int Int) (successor ::
 Int - State Int Int)
print (show b1 ++   ++ show b2)

 Running the code into ghci the result is False False. There is
 some old post saying that this is due to the dictionary-passing style 
 for
 typeclasses, and compiling with optimizations improves the situation.

 Compiling with ghc --make -O Tests.hs and running the program, the
 result is True True, which is what I expect.
 However, if I change main to be like the following:

  

Re: [Haskell-cafe] StableNames and monadic functions

2012-06-26 Thread Lorenzo Bolla
This is very tricky and it really depends on what you mean...
Formally, two functions are the same if they have the same domain and f(x)
== g(x) for each x in the domain. But this is not always
easy/feasible/efficient to implement! (See also
http://en.wikipedia.org/wiki/Rice%27s_theorem and
http://stackoverflow.com/questions/4844043/are-two-functions-equal.)

Depending on your problem, you might get away with just defining a
signature of your function and compare them: for example the signature
could be the concat of the function name, args types, etc. But I'm
speculating here...

L.



On Tue, Jun 26, 2012 at 4:50 PM, Ismael Figueroa Palet ifiguer...@gmail.com
 wrote:

 thanks again for your comments, any idea on how to implement Equivalence
 for functions?

 2012/6/26 Lorenzo Bolla lbo...@gmail.com

 In other words there is a difference between Identity and Equivalence.
 What you have implemented with StableName is an Identity (sometimes
 called reference equality), as opposed to an Equivalence (aka value
 equality).

 In Python, for example:

  x = {1:2}
  y = {1:2}
  x == y
 True
  x is y
 False

 L.


 On Tue, Jun 26, 2012 at 3:42 PM, Lorenzo Bolla lbo...@gmail.com wrote:

 I think about StableName like the  operator in C, that returns you
 the memory address of a variable. It's not the same for many reasons, but
 by analogy, if x == y then x == y, but x != y does not imply x != y.

 So, values that are semantically equal, may be stored in different
 memory locations and have different StableNames.

 The fact that changing the order of the lines also changes the result of
 the computation is obviously stated in the type signature of
 makeStableName, which lives in the IO monad. On the other hand
 hashStableNAme is a pure function.

 L.



 On Tue, Jun 26, 2012 at 3:26 PM, Ismael Figueroa Palet 
 ifiguer...@gmail.com wrote:



 2012/6/26 Lorenzo Bolla lbo...@gmail.com

 The point I was making is that StableName might be what you want. You
 are using it to check if two functions are the same by comparing their
 stablehash. But from StableName documentation:

  The reverse is not necessarily true: if two stable names are not
 equal, then the objects they name may still be equal.


 The `eq` you implemented means this, I reckon: if `eq` returns True
 then the 2 functions are equal, if `eq` returns False then you can't tell!

 Does it make sense?
 L.


 Yes  it does make sense, and I'm wondering why the hash are equal in
 one case but are not equal on the other case (i.e. using let/where vs not
 using it) because I'd like it to behave the same in both situations

 Thanks again




 On Tue, Jun 26, 2012 at 1:54 PM, Ismael Figueroa Palet 
 ifiguer...@gmail.com wrote:

 Thanks Lorenzo, I'm cc'ing the list with your response also:

 As you point out, when you do some kind of let-binding, using the
 where clause, or explicit let as in:

 main :: IO ()
 main = do
let f1 = (successor :: Int - State Int Int)
let f2 = (successor :: Int - Maybe Int)
b2 - eq f2 f2
b1 - eq f1 f1
print (show b1 ++   ++ show b2)

 The behavior is as expected. I guess the binding triggers some
 internal optimization or gives more information to the type checker; but
 I'm still not clear why it is required to be done this way -- having to
 let-bind every function is kind of awkward.

 I know the details of StableNames are probably
 implementation-dependent, but I'm still wondering about how to detect /
 restrict this situation.

 Thanks


 2012/6/26 Lorenzo Bolla lbo...@gmail.com

 From StableName docs:

 The reverse is not necessarily true: if two stable names are not
 equal, then the objects they name may still be equal.


 This version works as expected:

 import System.Mem.StableName
 import Control.Monad.State

 eq :: a - b - IO Bool
 eq a b = do
  pa - makeStableName a
  pb - makeStableName b
  return (hashStableName pa == hashStableName pb)

 successor :: (Num a, Monad m) = a - m a
 successor n = return (n+1)

 --  main :: IO ()
 --  main = do
 -- b2 - eq (successor :: Int - State Int Int) (successor
 :: Int - State Int Int)
 -- b1 - eq (successor :: Int - Maybe Int) (successor ::
 Int - Maybe Int)
 -- print (show b1 ++   ++ show b2)

 main :: IO ()
 main = do
b2 - eq f2 f2
b1 - eq f1 f1
print (show b1 ++   ++ show b2)
where f1 = (successor :: Int - Maybe Int)
  f2 = (successor :: Int - State Int Int)



 hth,
 L.




 On Tue, Jun 26, 2012 at 1:15 PM, Ismael Figueroa Palet 
 ifiguer...@gmail.com wrote:

 I'm using StableNames to have a notion of function equality, and
 I'm running into problems when using monadic functions.

 Consider the code below, file Test.hs

 import System.Mem.StableName
 import Control.Monad.State

 eq :: a - b - IO Bool
 eq a b = do
  pa - makeStableName a
  pb - makeStableName b
  return (hashStableName pa == hashStableName pb)

 

Re: [Haskell-cafe] HXT: Replace an element with its text

2012-06-26 Thread Michael Orlitzky
On 06/26/12 05:15, Ivan Perez wrote:
 Hi,
  You code fails because a link is not a node of kind Text, I think.
 What you want is to get the text from a child node of an anchor node.
 I think the following should work:

Yes, thank you. That makes sense now.


 process_link :: (ArrowXml a) = a XmlTree XmlTree
 process_link = getChildren  getText  mkText
 

This works!


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


Re: [Haskell-cafe] HXT: Replace an element with its text

2012-06-26 Thread Michael Orlitzky
On 06/26/12 10:39, Uwe Schmidt wrote:
 
 processTopDown $ (deep getText  mkText) `when` is_link
 
 should do it. The deep getText will find all Text nodes, independent
 of the nesting of elements in the a.../a element. If you then
 write the result into a document every thing is fine.
 
 One small problem can occur when the content of the a Element
 has e.g. the form
 
 bodya href=#foobbar/b/a/body
 
 The resulting DOM then still contains two text nodes, one for foo
 and one for bar. If you later search for a text foobar
 you don't find a node. The melting of adjacent text nodes can
 be done with
 
 ... (xshow (deep getText)  mkText) ...
 

Thanks for elaborating. This is just for display purposes, so hopefully
it won't be ever a problem. I'm parsing somebody else's HTML, though, so
who knows. I'll make a note in a comment.

Thanks again.


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


Re: [Haskell-cafe] StableNames and monadic functions

2012-06-26 Thread Ismael Figueroa Palet
Yes I agree, so far StableNames have been a good approximation, except for
the problem I described when using monads/class constraints :-(

2012/6/26 Lorenzo Bolla lbo...@gmail.com

 This is very tricky and it really depends on what you mean...
 Formally, two functions are the same if they have the same domain and f(x)
 == g(x) for each x in the domain. But this is not always
 easy/feasible/efficient to implement! (See also
 http://en.wikipedia.org/wiki/Rice%27s_theorem and
 http://stackoverflow.com/questions/4844043/are-two-functions-equal.)

 Depending on your problem, you might get away with just defining a
 signature of your function and compare them: for example the signature
 could be the concat of the function name, args types, etc. But I'm
 speculating here...

 L.



 On Tue, Jun 26, 2012 at 4:50 PM, Ismael Figueroa Palet 
 ifiguer...@gmail.com wrote:

 thanks again for your comments, any idea on how to implement
 Equivalence for functions?

 2012/6/26 Lorenzo Bolla lbo...@gmail.com

 In other words there is a difference between Identity and Equivalence.
 What you have implemented with StableName is an Identity (sometimes
 called reference equality), as opposed to an Equivalence (aka value
 equality).

 In Python, for example:

  x = {1:2}
  y = {1:2}
  x == y
 True
  x is y
 False

 L.


 On Tue, Jun 26, 2012 at 3:42 PM, Lorenzo Bolla lbo...@gmail.com wrote:

 I think about StableName like the  operator in C, that returns you
 the memory address of a variable. It's not the same for many reasons, but
 by analogy, if x == y then x == y, but x != y does not imply x != y.

 So, values that are semantically equal, may be stored in different
 memory locations and have different StableNames.

 The fact that changing the order of the lines also changes the result
 of the computation is obviously stated in the type signature of
 makeStableName, which lives in the IO monad. On the other hand
 hashStableNAme is a pure function.

 L.



 On Tue, Jun 26, 2012 at 3:26 PM, Ismael Figueroa Palet 
 ifiguer...@gmail.com wrote:



 2012/6/26 Lorenzo Bolla lbo...@gmail.com

 The point I was making is that StableName might be what you want. You
 are using it to check if two functions are the same by comparing their
 stablehash. But from StableName documentation:

  The reverse is not necessarily true: if two stable names are not
 equal, then the objects they name may still be equal.


 The `eq` you implemented means this, I reckon: if `eq` returns True
 then the 2 functions are equal, if `eq` returns False then you can't 
 tell!

 Does it make sense?
 L.


 Yes  it does make sense, and I'm wondering why the hash are equal in
 one case but are not equal on the other case (i.e. using let/where vs not
 using it) because I'd like it to behave the same in both situations

 Thanks again




 On Tue, Jun 26, 2012 at 1:54 PM, Ismael Figueroa Palet 
 ifiguer...@gmail.com wrote:

 Thanks Lorenzo, I'm cc'ing the list with your response also:

 As you point out, when you do some kind of let-binding, using the
 where clause, or explicit let as in:

 main :: IO ()
 main = do
let f1 = (successor :: Int - State Int Int)
let f2 = (successor :: Int - Maybe Int)
b2 - eq f2 f2
b1 - eq f1 f1
print (show b1 ++   ++ show b2)

 The behavior is as expected. I guess the binding triggers some
 internal optimization or gives more information to the type checker; but
 I'm still not clear why it is required to be done this way -- having to
 let-bind every function is kind of awkward.

 I know the details of StableNames are probably
 implementation-dependent, but I'm still wondering about how to detect /
 restrict this situation.

 Thanks


 2012/6/26 Lorenzo Bolla lbo...@gmail.com

 From StableName docs:

 The reverse is not necessarily true: if two stable names are not
 equal, then the objects they name may still be equal.


 This version works as expected:

 import System.Mem.StableName
 import Control.Monad.State

 eq :: a - b - IO Bool
 eq a b = do
  pa - makeStableName a
  pb - makeStableName b
  return (hashStableName pa == hashStableName pb)

 successor :: (Num a, Monad m) = a - m a
 successor n = return (n+1)

 --  main :: IO ()
 --  main = do
 -- b2 - eq (successor :: Int - State Int Int) (successor
 :: Int - State Int Int)
 -- b1 - eq (successor :: Int - Maybe Int) (successor ::
 Int - Maybe Int)
 -- print (show b1 ++   ++ show b2)

 main :: IO ()
 main = do
b2 - eq f2 f2
b1 - eq f1 f1
print (show b1 ++   ++ show b2)
where f1 = (successor :: Int - Maybe Int)
  f2 = (successor :: Int - State Int Int)



 hth,
 L.




 On Tue, Jun 26, 2012 at 1:15 PM, Ismael Figueroa Palet 
 ifiguer...@gmail.com wrote:

 I'm using StableNames to have a notion of function equality, and
 I'm running into problems when using monadic functions.

 Consider the code below, file Test.hs

 import System.Mem.StableName
 import 

[Haskell-cafe] Long-running request/response protocol server using enumerator/iterator/iterIO/pipes/conduits/...

2012-06-26 Thread Nicolas Trangez
Hello Cafe,

Some time ago I tried to implement a network service using iteratee (or
enumerator, can't remember), but gave up in the end. More recently I
wanted to create something similar (a similar protocol), but failed
again.

So I'm looking for some example code or something similar (Google only
helped slightly).

First of all, I don't care which API/library to use, I guess for my
purpose all of enumerator, iteratee, iterIO, pipes, conduits,... are OK,
so all feedback is welcome.

Here's the catch. Most examples out there implement some server which
accepts a single client request, interprets it, creates a response,
returns this, and closes the connection (or something alike, think
HTTP).

The protocol I'd like to implement is different: it's long-running using
repeated requests  responses on a single client connection. Basically,
a client connects and sends some data to the server (where the length of
this data is encoded in the header). Now the server reads  parses this
(binary) data, sets up some initial state for this client connection
(e.g. opening a file handle), and returns a reply. Now the client can
send another request, server parses/interprets it using the connection
state, sends a reply, and so on.

Might sound easy (and actually it's pretty easy in most other languages
I know, including an OCaml implementation), yet I fail to figure out how
to get this done using some enumerator-style library.

Thanks for any help, I'll most likely write up something if I get things
working for future reference.

Nicolas


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


Re: [Haskell-cafe] Long-running request/response protocol server using enumerator/iterator/iterIO/pipes/conduits/...

2012-06-26 Thread Christopher Done
On 26 June 2012 21:22, Nicolas Trangez nico...@incubaid.com wrote:
 Might sound easy (and actually it's pretty easy in most other languages
 I know, including an OCaml implementation), yet I fail to figure out how
 to get this done using some enumerator-style library.

Well, it's easy in Haskell, too. Just use the standard libraries.

If you want to mess around with these still-in-research iteratees and
eumerators for the composability then go for it, but when it's hard or
weird, you can't really blame that on the language. :-)

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


Re: [Haskell-cafe] Long-running request/response protocol server using enumerator/iterator/iterIO/pipes/conduits/...

2012-06-26 Thread Nicolas Trangez
On Tue, 2012-06-26 at 21:32 +0200, Christopher Done wrote:
 On 26 June 2012 21:22, Nicolas Trangez nico...@incubaid.com wrote:
  Might sound easy (and actually it's pretty easy in most other languages
  I know, including an OCaml implementation), yet I fail to figure out how
  to get this done using some enumerator-style library.
 
 Well, it's easy in Haskell, too. Just use the standard libraries.

Sure, that could work.

 If you want to mess around with these still-in-research iteratees and
 eumerators for the composability then go for it, but when it's hard or
 weird, you can't really blame that on the language. :-)

Make no mistake, I'm not blaming anything except my own inability to
figure this out ;-)

Thanks,

Nicolas


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


Re: [Haskell-cafe] Long-running request/response protocol server using enumerator/iterator/iterIO/pipes/conduits/...

2012-06-26 Thread Michael Snoyman
On Tue, Jun 26, 2012 at 10:22 PM, Nicolas Trangez nico...@incubaid.com wrote:
 Hello Cafe,

 Some time ago I tried to implement a network service using iteratee (or
 enumerator, can't remember), but gave up in the end. More recently I
 wanted to create something similar (a similar protocol), but failed
 again.

 So I'm looking for some example code or something similar (Google only
 helped slightly).

 First of all, I don't care which API/library to use, I guess for my
 purpose all of enumerator, iteratee, iterIO, pipes, conduits,... are OK,
 so all feedback is welcome.

 Here's the catch. Most examples out there implement some server which
 accepts a single client request, interprets it, creates a response,
 returns this, and closes the connection (or something alike, think
 HTTP).

 The protocol I'd like to implement is different: it's long-running using
 repeated requests  responses on a single client connection. Basically,
 a client connects and sends some data to the server (where the length of
 this data is encoded in the header). Now the server reads  parses this
 (binary) data, sets up some initial state for this client connection
 (e.g. opening a file handle), and returns a reply. Now the client can
 send another request, server parses/interprets it using the connection
 state, sends a reply, and so on.

 Might sound easy (and actually it's pretty easy in most other languages
 I know, including an OCaml implementation), yet I fail to figure out how
 to get this done using some enumerator-style library.

 Thanks for any help, I'll most likely write up something if I get things
 working for future reference.

 Nicolas


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

I've run into those kinds of problems in the past as well. In general,
interleaving of data streams can be difficult with enumerator. That's
the reason I added connect-and-resume to conduit. I use the technique
in warp[1], which in fact *does* support multiple request/response
pairs due to connection keep-alive. But the code base isn't the
easiest introduction to the technique. If there's interest, I'll try
to put together a blog post on using connect-and-resume to solve this
kind of problem.

Michael

[1] 
https://github.com/yesodweb/wai/blob/beta/warp/Network/Wai/Handler/Warp.hs#L296

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


Re: [Haskell-cafe] Long-running request/response protocol server using enumerator/iterator/iterIO/pipes/conduits/...

2012-06-26 Thread Paolo Capriotti
On Tue, Jun 26, 2012 at 8:22 PM, Nicolas Trangez nico...@incubaid.com wrote:
 Hello Cafe,

 Some time ago I tried to implement a network service using iteratee (or
 enumerator, can't remember), but gave up in the end. More recently I
 wanted to create something similar (a similar protocol), but failed
 again.

 So I'm looking for some example code or something similar (Google only
 helped slightly).

 First of all, I don't care which API/library to use, I guess for my
 purpose all of enumerator, iteratee, iterIO, pipes, conduits,... are OK,
 so all feedback is welcome.

 Here's the catch. Most examples out there implement some server which
 accepts a single client request, interprets it, creates a response,
 returns this, and closes the connection (or something alike, think
 HTTP).

 The protocol I'd like to implement is different: it's long-running using
 repeated requests  responses on a single client connection. Basically,
 a client connects and sends some data to the server (where the length of
 this data is encoded in the header). Now the server reads  parses this
 (binary) data, sets up some initial state for this client connection
 (e.g. opening a file handle), and returns a reply. Now the client can
 send another request, server parses/interprets it using the connection
 state, sends a reply, and so on.

 Might sound easy (and actually it's pretty easy in most other languages
 I know, including an OCaml implementation), yet I fail to figure out how
 to get this done using some enumerator-style library.

With the current development version of pipes-core
(https://github.com/pcapriotti/pipes-core/tree/devel) I would write something
like the following (completely untested) code:

import qualified Control.Pipe.Binary as B
...

request :: PipeL IO ByteString ByteString u ()
request = do
h - header
let n = hdrSize h
B.take n

-- I assume a fixed-size header for simplicity
header :: PipeL IO ByteString b u Header
header = do
h - B.take headerSize + fold () ByteString.empty
return $ parseHeader h -- the function doing the actual parsing

handler :: Pipe IO ByteString ByteString u ()
handler = do
-- server logic here
-- just echo the input data as an example
void idP

server hInput hOutput
   -- read from the socket
 = B.handleReader hInput
   -- process all requests
   + forever (withUnawait $ request + handler)
   -- write to socket
   + B.handleWriter hOutput

Requests are handled sequentially by the `forever` loop. This whole pipeline
works with chunks of data represented as `ByteString`s, and `PipeL` (a new
feature of pipes-core 0.2.0) is used to pass leftover data along.

In a real implementation, you would also probably need to wrap `handler` in
something like:

catch handler $ \e -
liftIO $ logException e
discard

so that failures (or early termination) in `handler` don't bring the whole
pipeline down.

Sorry for the not very practical reply, involving experimental
unreleased code. :)

BR,
Paolo

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


Re: [Haskell-cafe] Long-running request/response protocol server using enumerator/iterator/iterIO/pipes/conduits/...

2012-06-26 Thread Nicolas Trangez
On Tue, 2012-06-26 at 22:39 +0300, Michael Snoyman wrote:
 I've run into those kinds of problems in the past as well. In general,
 interleaving of data streams can be difficult with enumerator. That's
 the reason I added connect-and-resume to conduit. I use the technique
 in warp[1], which in fact *does* support multiple request/response
 pairs due to connection keep-alive. But the code base isn't the
 easiest introduction to the technique. If there's interest, I'll try
 to put together a blog post on using connect-and-resume to solve this
 kind of problem.

Thank you, Michael. I thought about HTTP keep-alive as well, but felt
reluctant to start by looking at a 'large' codebase like warp... Anyway,
what you point to seems reasonable to interpret, I should be able to
write something similar based on this (even though I never used
Conduits/ResourceT before).

Thanks!

Nicolas


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


Re: [Haskell-cafe] Unambiguous choice implementation

2012-06-26 Thread Bartosz Milewski
I see. So you're current implementation is not push, is it? The original
pull implementation in Fran also used Maybe events, but that was considered
inefficient. How is Reactive Banana better then Fran then?

--Bartosz

On Tue, Jun 26, 2012 at 1:40 AM, Heinrich Apfelmus 
apfel...@quantentunnel.de wrote:

 Bartosz Milewski wrote:

 Thanks, Heinrich. I looked at the examples and at the references you
 provided. I understand the semantic model, so I guess I'm mostly trying to
 understand the implementation.


 Ok. As I mentioned, if you just want to use the library there is no need
 to understand the implementation.


  Conal's paper was mostly about refining data
 structures in order to provide better implementation. It's all beautiful
 up
 to the point where he introduces the unamb hack. How did you manage to
 work
 around this problem and implement event merging efficiently?


 Essentially, Conal implements events as

type Event a = [(Time,a)]

 The trouble is that when merging events, this representation forces you to
 wait for both events. In other words, the pattern match

union ((t1,x1):e1) ((t2,x2):e2) = ...

 needs to know the times of occurrences of both events before it can return
 the earlier one. The trouble is that the  merge  function should have
 returned the earlier one right away, before knowing exactly when the later
 one happens. The purpose of the  unamb  hack is circumvent that problem.


 Reactive-banana's very simple solution to this problem is to represent
 events as

type Event a = [(Time, Maybe a)]

 and impose the additional invariant that all events in your program are
 synchronized, in the sense that they indicate their occurrences at the
 same times^1. If they don't occur at that time, they use  Nothing . Then,
 you can implement  merge  simply as

union ((t1,x1):e1) ((t2,x2):e2) = -- we always have  t1 = t2
(t1, combine x1 x2) : union e1 e2
where
combine (Just x) Nothing  = Just x   -- only left occurs
combine Nothing  (Just y) = Just y   -- only right occurs
combine (Just x) (Just y) = Just x   -- simultaneous occurrence
combine Nothing  Nothing  = Nothing  -- neither occurs

 Since the times are given globally, we can also remove them and obtain

type Event a = [Maybe a]

 This is how  Reactive.Banana.Model  does it.


 Of course, keeping track of a lot of  Nothing  is something that can be
 optimized. The optimization to apply here is to transform the
 implementation into a push-driven style. I haven't published the details
 yet, but some design notes can be found here.

 http://apfelmus.nfshost.com/**blog/2011/04/24-frp-push-**
 driven-sharing.htmlhttp://apfelmus.nfshost.com/blog/2011/04/24-frp-push-driven-sharing.html


 ^1: Note that the times do not need to follow a uniform time step.



 Best regards,
 Heinrich Apfelmus

 --
 http://apfelmus.nfshost.com


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

 --
 You received this message because you are subscribed to the Google Groups
 Haskell-cafe group.
 To post to this group, send email to haskell-c...@googlegroups.com.
 To unsubscribe from this group, send email to haskell-cafe+unsubscribe@**
 googlegroups.com haskell-cafe%2bunsubscr...@googlegroups.com.
 For more options, visit this group at http://groups.google.com/**
 group/haskell-cafe?hl=enhttp://groups.google.com/group/haskell-cafe?hl=en
 .




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


Re: [Haskell-cafe] Martin Odersky on What's wrong with Monads

2012-06-26 Thread Tillmann Rendel

Hi,

MightyByte wrote:

Of course every line of your program that uses a Foo will change if you switch
to IO Foo instead.


But we often have to also change lines that don't use Foo at all. For 
example, here is the type of binary trees of integers:


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

A function to add up all integers in a tree:

  amount:: Tree - Integer
  amount (Leaf x) = x
  amount (Branch t1 t2) = amountt1 + amountt2

All fine so far. Now, consider the following additional requirement: If 
the command-line flag --multiply is set, the function amount computes 
the product instead of the sum.


In a language with implicit side effects, it is easy to implement this. 
We just change the third line of the amount function to check whether to 
call (+) or (*). In particular, we would not touch the other two lines.


How would you implement this requirement in Haskell without changing the 
line amount (Leaf x) = x?


(I actually see three ways of doing this in Haskell, but all have 
serious drawbacks and do not fully solve the problem).


Here it seems not so bad just to change all three lines of the amount 
function, even if they are not strictly related to the semantic change 
we want to make. But in a real program, this situation can translate to 
changing thousands of lines of code in many functions just to implement 
a minor change to a single requirement.


  Tillmann

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


Re: [Haskell-cafe] Martin Odersky on What's wrong with Monads

2012-06-26 Thread Ozgun Ataman
We could debate this endlessly (as is common), but I would argue that a clean 
design would make the option and alternative of multiplying explicit in its 
design instead of including calls to fetch command line arguments in an ad-hoc 
fashion everywhere. 

The Haskell way of encoding this would be to define an app configuration data 
type (say AppConfig), parse the command line arguments into it upfront in IO 
and then run your application either in a in a monad that's an instance of 
(MonadReader MyConfig) or explicitly pass the option in where needed by a 
function. If you've designed your application this way, adding a new command 
line option would cause very little -if any- refactoring. If not, in my 
experience it is usually a 30 minute intense refactoring campaign.

I suspect there might be a way to use implicit arguments here as well, but 
that's something I've never felt compelled to use.

This kind of separation of concerns and pure application design is one of the 
things that (I think) many people really like about Haskell.

Cheers,
Oz


On Tuesday, June 26, 2012 at 6:19 PM, Tillmann Rendel wrote:

 Hi,
 
 MightyByte wrote:
  Of course every line of your program that uses a Foo will change if you 
  switch
  to IO Foo instead.
  
 
 
 But we often have to also change lines that don't use Foo at all. For 
 example, here is the type of binary trees of integers:
 
 data Tree = Leaf Integer | Branch (Tree Integer) (Tree Integer)
 
 A function to add up all integers in a tree:
 
 amount:: Tree - Integer
 amount (Leaf x) = x
 amount (Branch t1 t2) = amountt1 + amountt2
 
 All fine so far. Now, consider the following additional requirement: If 
 the command-line flag --multiply is set, the function amount computes 
 the product instead of the sum.
 
 In a language with implicit side effects, it is easy to implement this. 
 We just change the third line of the amount function to check whether to 
 call (+) or (*). In particular, we would not touch the other two lines.
 
 How would you implement this requirement in Haskell without changing the 
 line amount (Leaf x) = x?
 
 (I actually see three ways of doing this in Haskell, but all have 
 serious drawbacks and do not fully solve the problem).
 
 Here it seems not so bad just to change all three lines of the amount 
 function, even if they are not strictly related to the semantic change 
 we want to make. But in a real program, this situation can translate to 
 changing thousands of lines of code in many functions just to implement 
 a minor change to a single requirement.
 
 Tillmann
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org (mailto: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] Martin Odersky on What's wrong with Monads

2012-06-26 Thread Patrick Hurst
I'd also say that reading command-line flags inside a simple function like
amount is a pretty large code smell. The only case in which it isn't would
be when the codebase is so small that redesigning the Haskell to be in IO
(or switch between amountPlus and amountTimes) is negligible anyway.

On Jun 26, 2012, at 18:59, Ozgun Ataman ozata...@gmail.com wrote:

We could debate this endlessly (as is common), but I would argue that a
clean design would make the option and alternative of multiplying
explicit in its design instead of including calls to fetch command line
arguments in an ad-hoc fashion everywhere.

The Haskell way of encoding this would be to define an app configuration
data type (say AppConfig), parse the command line arguments into it upfront
in IO and then run your application either in a in a monad that's an
instance of (MonadReader MyConfig) or explicitly pass the option in where
needed by a function. If you've designed your application this way, adding
a new command line option would cause very little -if any- refactoring. If
not, in my experience it is usually a 30 minute intense refactoring
campaign.

I suspect there might be a way to use implicit arguments here as well, but
that's something I've never felt compelled to use.

This kind of separation of concerns and pure application design is one of
the things that (I think) many people really like about Haskell.

Cheers,
Oz

On Tuesday, June 26, 2012 at 6:19 PM, Tillmann Rendel wrote:

Hi,

MightyByte wrote:

Of course every line of your program that uses a Foo will change if you
switch
to IO Foo instead.


But we often have to also change lines that don't use Foo at all. For
example, here is the type of binary trees of integers:

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

A function to add up all integers in a tree:

amount:: Tree - Integer
amount (Leaf x) = x
amount (Branch t1 t2) = amountt1 + amountt2

All fine so far. Now, consider the following additional requirement: If
the command-line flag --multiply is set, the function amount computes
the product instead of the sum.

In a language with implicit side effects, it is easy to implement this.
We just change the third line of the amount function to check whether to
call (+) or (*). In particular, we would not touch the other two lines.

How would you implement this requirement in Haskell without changing the
line amount (Leaf x) = x?

(I actually see three ways of doing this in Haskell, but all have
serious drawbacks and do not fully solve the problem).

Here it seems not so bad just to change all three lines of the amount
function, even if they are not strictly related to the semantic change
we want to make. But in a real program, this situation can translate to
changing thousands of lines of code in many functions just to implement
a minor change to a single requirement.

Tillmann

___
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] Haskell-Cafe Digest, Vol 106, Issue 38

2012-06-26 Thread John Lato
 Message: 12
 Date: Wed, 27 Jun 2012 00:19:30 +0200
 From: Tillmann Rendel ren...@informatik.uni-marburg.de
 Subject: Re: [Haskell-cafe] Martin Odersky on What's wrong with
        Monads
 Cc: haskell-cafe@haskell.org
 Message-ID: 4fea3572.5060...@informatik.uni-marburg.de
 Content-Type: text/plain; charset=ISO-8859-1; format=flowed

 Hi,

 MightyByte wrote:
 Of course every line of your program that uses a Foo will change if you 
 switch
 to IO Foo instead.

 But we often have to also change lines that don't use Foo at all. For
 example, here is the type of binary trees of integers:

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

 A function to add up all integers in a tree:

   amount:: Tree - Integer
   amount (Leaf x) = x
   amount (Branch t1 t2) = amountt1 + amountt2

 All fine so far. Now, consider the following additional requirement: If
 the command-line flag --multiply is set, the function amount computes
 the product instead of the sum.

 In a language with implicit side effects, it is easy to implement this.
 We just change the third line of the amount function to check whether to
 call (+) or (*). In particular, we would not touch the other two lines.

 How would you implement this requirement in Haskell without changing the
 line amount (Leaf x) = x?

Why would you do that even in an imperative language?  The program
logic turns into a spaghetti mess, and it's much harder to test.

I would write Tree like this:

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

and instead of an amount function I would use a fold.  If you like,
you can use ala from Control.Newtype

*Main Data.Foldable Data.Monoid let t1 = Branch (Leaf 1) (Branch
(Leaf 4) (Leaf 5)) :: Tree Int
*Main Data.Foldable Data.Monoid ala Sum foldMap t1
10
*Main Data.Foldable Data.Monoid ala Product foldMap t1
20

Now the amount calculation can be something like

amount :: Num a = Tree a - IO a
amount tree = multFlag = \b - if b then ala Product foldMap tree
else ala Sum foldMap tree


although I probably wouldn't actually write it unless it was called in
more than one place.  There are other ways to write it too; the
important part is that checking the configuration is completely
separate from the tree traversal.

Plus, if it changes again (now there's another flag that says to
ignore values == n or something, you can use the same fold, just
change the function that's passed to it (or the monoid instance if
you're using that).

Plus, this type of code is much simpler to debug, test, and maintain
than imperative-style magic functions.

Cheers,
John

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


Re: [Haskell-cafe] Haskell-Cafe Digest, Vol 106, Issue 38

2012-06-26 Thread Richard O'Keefe

On 27/06/2012, at 12:51 PM, John Lato wrote:
 
 data Tree a = Leaf a | Branch (Tree a) ( Tree a)
  deriving (Foldable, Show)

While I am familiar with deriving (Show),
I am not familiar with deriving (Foldable),
which looks rather useful.

http://www.haskell.org/ghc/docs/7.4.2/html/users_guide/deriving.html
just says With -XDeriveFoldable, you can derive instances of the
class Foldable, defined in Data.Foldable. but it provides no details.

Would you care to explain more about deriving (Foldable)?


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


Re: [Haskell-cafe] Martin Odersky on What's wrong with Monads

2012-06-26 Thread Nathan Howell
On Tue, Jun 26, 2012 at 3:19 PM, Tillmann Rendel
ren...@informatik.uni-marburg.de wrote:
 A function to add up all integers in a tree:

  amount:: Tree - Integer
  amount (Leaf x) = x
  amount (Branch t1 t2) = amountt1 + amountt2

 All fine so far. Now, consider the following additional requirement: If the
 command-line flag --multiply is set, the function amount computes the
 product instead of the sum.

 How would you implement this requirement in Haskell without changing the
 line amount (Leaf x) = x?

One option is to encode the desired behavior at the type level. By
extended the data type slightly and adding a Functor instance,
selecting between a product and a sum can be done using their Monoid
newtypes:

import Data.Monoid
import System.Environment

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

instance Functor Tree where
  f `fmap` Leaf x = Leaf (f x)
  f `fmap` Branch x y = Branch (fmap f x) (fmap f y)

amount :: Monoid a = Tree a - a
amount (Leaf x) = x
amount (Branch t1 t2) = amount t1  amount t2

main :: IO ()
main = do
  args - getArgs

  let val :: Tree Int
  val = Branch (Leaf 8) (Leaf 18)

  let getResult :: Tree Int - Int
  getResult = case args of
[--multiply] - getProduct . amount . fmap Product
_  - getSum . amount . fmap Sum

  print . getResult $ val

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


Re: [Haskell-cafe] Haskell-Cafe Digest, Vol 106, Issue 38

2012-06-26 Thread John Lato
On Wed, Jun 27, 2012 at 9:15 AM, Richard O'Keefe o...@cs.otago.ac.nz wrote:

 On 27/06/2012, at 12:51 PM, John Lato wrote:

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

 While I am familiar with deriving (Show),
 I am not familiar with deriving (Foldable),
 which looks rather useful.

 http://www.haskell.org/ghc/docs/7.4.2/html/users_guide/deriving.html
 just says With -XDeriveFoldable, you can derive instances of the
 class Foldable, defined in Data.Foldable. but it provides no details.

 Would you care to explain more about deriving (Foldable)?

There's not much to explain, DeriveFoldable basically does just that;
automatically provide an instance of the Foldable class for a data
type.  I think the original proposal for DeriveFoldable was from Twan
van Laarhoven, 
http://www.mail-archive.com/haskell-prime@haskell.org/msg02116.html,
and there's a little bit of history on GHC's trac,
http://hackage.haskell.org/trac/ghc/ticket/2953.  The current
implementation probably hasn't changed much since Simon PJ's original
patch, although there's probably substantial overlap with ghc's
generics these days.

As for the Foldable class itself, the docs at
http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data-Foldable.html
are pretty good.  It lets you perform a number of folds (left, right,
monoidal) over arbitrary datatypes, not just lists.

I think that's about it.  Although I'm not the best person to explain
either the DeriveFoldable algorithm or the different uses of folds;
maybe someone else would be able to fill in anything I've missed.

John L.

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


Re: [Haskell-cafe] Haskell-Cafe Digest, Vol 106, Issue 38

2012-06-26 Thread Richard O'Keefe

On 27/06/2012, at 3:18 PM, John Lato wrote:

 On Wed, Jun 27, 2012 at 9:15 AM, Richard O'Keefe o...@cs.otago.ac.nz wrote:
 
 On 27/06/2012, at 12:51 PM, John Lato wrote:
 
 data Tree a = Leaf a | Branch (Tree a) ( Tree a)
  deriving (Foldable, Show)
 
 While I am familiar with deriving (Show),
 I am not familiar with deriving (Foldable),
 which looks rather useful.
 
 http://www.haskell.org/ghc/docs/7.4.2/html/users_guide/deriving.html
 just says With -XDeriveFoldable, you can derive instances of the
 class Foldable, defined in Data.Foldable. but it provides no details.
 
 Would you care to explain more about deriving (Foldable)?
 
 There's not much to explain, DeriveFoldable basically does just that;
 automatically provide an instance of the Foldable class for a data
 type.

That was sufficiently obvious, yes.
The question remains, ***WHAT*** instance?

  I think the original proposal for DeriveFoldable was from Twan
 van Laarhoven, 
 http://www.mail-archive.com/haskell-prime@haskell.org/msg02116.html,

which goes into a great deal of detail about what deriving (Functor)
does, but none whatsoever about what deriving (Foldable) does.  Even
for Functor, another 3 or 4 nontrivial examples would be nice.

 and there's a little bit of history on GHC's trac,
 http://hackage.haskell.org/trac/ghc/ticket/2953.  The current
 implementation probably hasn't changed much since Simon PJ's original
 patch, although there's probably substantial overlap with ghc's
 generics these days.

That trac entry contains one sentence that seems to still apply:

  What is missing is a section in the user manual describing the changes.

It refers to section 8.5, which is now 7.5, and there is still no
adequate documentation there.
 
 As for the Foldable class itself, the docs at
 http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data-Foldable.html
 are pretty good. 

Yes, Foldable *is* documented.
However, that page says nothing whatever about deriving (Foldable).




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