Re: [Haskell-cafe] using the writer monad to better understand foldl and foldr, and haskell debugging techniques in general

2008-02-11 Thread Felipe Lessa
On Feb 10, 2008 9:52 PM, Thomas Hartman [EMAIL PROTECTED] wrote:
 So, I would say this proves my main point, which was that you could
 accomplish the same thing using the writer monad that you could do
 using the more ad hoc trace function from Debug.Trace.

Not really. That only happens with your implementation of myfoldrD. If
you write it as

myfoldrD' f z [] = z
myfoldrD' f z (x:xs) = x `f` trace (x,r:  ++ (show (x,r))) r
where r = myfoldrD' f z xs

then we have the expected behavior

*Main myfoldrD (:) [] [1..5]
x,r: (5,[])
x,r: (4,[5])
x,r: (3,[4,5])
x,r: (2,[3,4,5])
x,r: (1,[2,3,4,5])
[1,2,3,4,5]
*Main myfoldrD' (:) [] [1..5]
[1x,r: (5,[])
x,r: (4,[5])
x,r: (3,[4,5])
x,r: (2,[3,4,5])
x,r: (1,[2,3,4,5])
,2,3,4,5]
*Main myfoldrD const 0 [1..]
Interrupted.
*Main myfoldrD' const 0 [1..]
1
*Main myfoldrD (\x xs - if x  0 then [] else x:xs) [] ([1,2,3,-1]
++ repeat 0)
*** Exception: stack overflow
*Main myfoldrD' (\x xs - if x  0 then [] else x:xs) [] ([1,2,3,-1]
++ repeat 0)
[1x,r: (3,[])
x,r: (2,[3])
x,r: (1,[2,3])
,2,3]

As Debug.Trace hides the IO monad in a pure computation (i.e.
unsafePerformIO) we can use it from the inside of the [pure] function
that is passed to foldr.

Note that we could also implement a Writer monad on top of
unsafePerformIO, you basically just change Debug.Trace to an IO action
that does the mappend as Writer would but in an IORef. In the end you
read that IORef and do a big tell to the outside Writer monad. I'd say
that this is a safe use of unsafePerformIO as it shouldn't break
referential transparency. But without this hack I don't think we could
do the same thing. Good news is that the hack is 'hideable' as are the
hacks from ByteString, for example.

Cheers,

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


Re: [Haskell-cafe] using the writer monad to better understand foldl and foldr, and haskell debugging techniques in general

2008-02-10 Thread Thomas Hartman
same behavior with

myfoldrD (:) [] [1..] -- uses Debug.Trace.trace

So, I would say this proves my main point, which was that you could
accomplish the same thing using the writer monad that you could do
using the more ad hoc trace function from Debug.Trace.

It's good that you point this out though, because understanding that
foldr can take an infinite list and foldl not is a very key point.


 2008/2/10, Felipe Lessa [EMAIL PROTECTED]:
  On Feb 10, 2008 9:33 PM, Thomas Hartman [EMAIL PROTECTED] wrote:
   -- using writer monad
   -- Nothing unsafe here, pure referrentially transparent goodness
   myfoldrW f z [] =  return z
   myfoldrW f z (x:xs) = do
   r - (myfoldrW f z xs)
   tell (x,r:  ++ (show (x,r)) ++ \n )
   return $ x `f` r
 
  *Main foldr const 0 [1..]
  1
  *Main putStrLn $ snd $ runWriter $ myfoldrW const 0 [1..]
  Interrupted.
 
  One of the good things from foldr is the possibility of
  short-circuiting, so to speak. However I don't know if it is
  possible to show this using the writer monad, as is would involve
  observing if the function is strict or not in its second argument.
 
  Cheers,
 
  --
  Felipe.
 

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


Re: [Haskell-cafe] using the writer monad to better understand foldl and foldr, and haskell debugging techniques in general

2008-02-10 Thread Felipe Lessa
On Feb 10, 2008 9:33 PM, Thomas Hartman [EMAIL PROTECTED] wrote:
 -- using writer monad
 -- Nothing unsafe here, pure referrentially transparent goodness
 myfoldrW f z [] =  return z
 myfoldrW f z (x:xs) = do
 r - (myfoldrW f z xs)
 tell (x,r:  ++ (show (x,r)) ++ \n )
 return $ x `f` r

*Main foldr const 0 [1..]
1
*Main putStrLn $ snd $ runWriter $ myfoldrW const 0 [1..]
Interrupted.

One of the good things from foldr is the possibility of
short-circuiting, so to speak. However I don't know if it is
possible to show this using the writer monad, as is would involve
observing if the function is strict or not in its second argument.

Cheers,

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


[Haskell-cafe] using the writer monad to better understand foldl and foldr, and haskell debugging techniques in general

2008-02-10 Thread Thomas Hartman
The following is a simple introduction to debugging techniques in
haskell, illustrated with a canonical use of foldr and foldl.

Comments welcome.

import Control.Monad.Writer
import Debug.Trace
-- We use the writer monad to better understand foldl and foldr
-- and show a debugging technique in haskell
-- you could get similar output using Debug.Trace, but this relies on
unsafePerformIO
-- ... 
http://www.haskell.org/ghc/docs/latest/html/libraries/base/src/Debug-Trace.html
-- which is Ugly.
-- Though ugly, trace isn't really unsafe as far as my understanding
goes. But still, I find it nice
-- that there's a way to accomplish the exact same thing by using the
writer or debugger monad
-- which is pure as pure can get

-- In this particular example, it doesn't matter if you use
Debug.Trace or the writer monad.
-- However, I am fidding around in another scenario (debugging a
series of graphs using Data.Graph.Inductive)
-- which seems not to lend itself well to trace. If I can find a nice
way to explain what I am doing and why
-- I may do a follow-up to this post describing that.

-- same as prelude, I think
myfoldr f z [] =  z
myfoldr f z (x:xs) =  x `f` r
  where r = (myfoldr f z xs)
myfoldl f z [] = z
myfoldl f z (x:xs) = myfoldl f l xs
  where l = z `f` x

-- canonical uses of fold, no debug output
tfr = myfoldr (:) [] [1..10] -- copy a list
tfl = myfoldl (flip (:)) [] [1..10] -- reverse a list

-- debugging output using Debug.Trace (unsafePerfomIO)
-- (Not really unsafe, but unsafePerformIO (which is used in the trace
function) sounds kind of scary)
myfoldrD f z [] =  z
myfoldrD f z (x:xs) | trace (x,r:  ++ (show (x,r))) True =  x `f` r
  where r = (myfoldrD f z xs)
myfoldlD f z [] = z
myfoldlD f z (x:xs) | trace ((z,x) ++ (show (z,x))) True= myfoldlD f l xs
  where l = z `f` x

-- run these to see the functions with debug output from trace
tfrD = myfoldrD (:) [] [1..10] -- copy a list
tflD = myfoldlD (flip (:)) [] [1..10] -- reverse a list

-- using writer monad
-- Nothing unsafe here, pure referrentially transparent goodness
myfoldrW f z [] =  return z
myfoldrW f z (x:xs) = do
r - (myfoldrW f z xs)
tell (x,r:  ++ (show (x,r)) ++ \n )
return $ x `f` r

myfoldlW f z [] = return z
myfoldlW f z (x:xs) = do
  tell (z,x):  ++ (show (z,x)) ++ \n)
  l - return $ (z `f` x)
  myfoldlW f l xs

-- display the debug output from the writer monad
tfrW = putStrLn $ snd $ runWriter $ myfoldrW (:) [] [1..10]
tflW = putStrLn $ snd $ runWriter $ myfoldlW (flip (:)) [] [1..10]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe