Re: [Haskell-cafe] Re: Embedding newlines into a string?

2008-04-18 Thread Ariel J. Birnbaum
 Things to avoid - HaskellWiki - 7 Related Links:
 http://www.haskell.org/haskellwiki/Things_to_avoid#Related_Links
The link was broken (it had an extra chunk of '- Haskell Wiki' ;) )
so I fixed it. For that matter, the Common Hugs Messages link is
broken too but I can't seem to find the page it should point to.
-- 
Ariel J. Birnbaum
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Embedding newlines into a string?

2008-04-18 Thread Benjamin L. Russell
Ariel,

--- Ariel J. Birnbaum [EMAIL PROTECTED] wrote:

  Things to avoid - HaskellWiki - 7 Related Links:
 

http://www.haskell.org/haskellwiki/Things_to_avoid#Related_Links
 The link was broken (it had an extra chunk of '-
 Haskell Wiki' ;) )
 so I fixed it.

Thank you; sorry about the broken link.

 For that matter, the Common Hugs
 Messages link is
 broken too but I can't seem to find the page it
 should point to.

I just fixed it.  It was supposed to be an external
link to the following Web page:

Some common Hugs error messages
http://www.cs.kent.ac.uk/people/staff/sjt/craft2e/errors/allErrors.html

I discovered that link originally under the following
subsection of HaskellWiki:

Learning Haskell - 2 Material - 2.9 Reference
http://www.haskell.org/haskellwiki/Learning_Haskell#Reference

This time, I have checked my updated link to verify
that it works. ;-)

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


Re: [Haskell-cafe] Re: Embedding newlines into a string?

2008-04-17 Thread Ariel J. Birnbaum
 Common Misunderstandings - HaskellWiki
 http://www.haskell.org/haskellwiki/Common_Misunderstandings
I didn't find this one... maybe it should be in a more prominent place?

 Things to avoid - HaskellWiki
 http://www.haskell.org/haskellwiki/Things_to_avoid
I thought of this but it has more discussions about style than pitfalls...
it seems to me more oriented to people who know Haskell well and want to
write better.
Maybe a link from here to the above would be a good idea.

Thanks for adding this case to the wiki =)

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


Re: [Haskell-cafe] Re: Embedding newlines into a string?

2008-04-17 Thread Benjamin L. Russell
Ariel,

--- Ariel J. Birnbaum [EMAIL PROTECTED] wrote:

  Common Misunderstandings - HaskellWiki
 

http://www.haskell.org/haskellwiki/Common_Misunderstandings
 I didn't find this one... maybe it should be in a
 more prominent place?
 
  Things to avoid - HaskellWiki
  http://www.haskell.org/haskellwiki/Things_to_avoid
 I thought of this but it has more discussions about
 style than pitfalls...
 it seems to me more oriented to people who know
 Haskell well and want to
 write better.
 Maybe a link from here to the above would be a good
 idea.

Added:

Things to avoid - HaskellWiki - 7 Related Links:
http://www.haskell.org/haskellwiki/Things_to_avoid#Related_Links

 Thanks for adding this case to the wiki =)

My pleasure!

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


Re: [Haskell-cafe] Re: Embedding newlines into a string?

2008-04-16 Thread Ariel J. Birnbaum
 That's exactly what I was thinking about, but your hanoi_shower only
 handles list of exactly one action, but you have to handle longer lists,
 too. This could be done with explicit recursion

This seems to be a common pitfall for Haskell newcomers: mistaking
a single-element list pattern (such as [x]) for a pattern that iterates
over every element in the list.
I can't seem to find a page with a list of common pitfalls and mistakes...
is there such a thing?

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


Re: [Haskell-cafe] Re: Embedding newlines into a string?

2008-04-16 Thread Benjamin L. Russell
Ariel,

Check out the following HaskellWiki pages:

Common Misunderstandings - HaskellWiki
http://www.haskell.org/haskellwiki/Common_Misunderstandings

Things to avoid - HaskellWiki
http://www.haskell.org/haskellwiki/Things_to_avoid

Hope these help

Benjamin L. Russell

--- Ariel J. Birnbaum [EMAIL PROTECTED] wrote:

  That's exactly what I was thinking about, but your
 hanoi_shower only
  handles list of exactly one action, but you have
 to handle longer lists,
  too. This could be done with explicit recursion
 
 This seems to be a common pitfall for Haskell
 newcomers: mistaking
 a single-element list pattern (such as [x]) for a
 pattern that iterates
 over every element in the list.
 I can't seem to find a page with a list of common
 pitfalls and mistakes...
 is there such a thing?
 
 -- 
 Ariel J. Birnbaum
 ___
 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] Re: Embedding newlines into a string?

2008-04-16 Thread Benjamin L. Russell
Ariel,

In response to your comment, since there was
apparently no section devoted to pitfalls of iterating
over lists, I have added the section 1.4 Iterating
Over a List in the following HaskellWiki page; viz:

Common Misunderstandings - HaskellWiki
http://www.haskell.org/haskellwiki/Common_Misunderstandings#Iterating_Over_a_List

Hope this helps

Benjamin L. Russell

--- Benjamin L. Russell [EMAIL PROTECTED]
wrote:

 Ariel,
 
 Check out the following HaskellWiki pages:
 
 Common Misunderstandings - HaskellWiki

http://www.haskell.org/haskellwiki/Common_Misunderstandings
 
 Things to avoid - HaskellWiki
 http://www.haskell.org/haskellwiki/Things_to_avoid
 
 Hope these help
 
 Benjamin L. Russell
 
 --- Ariel J. Birnbaum [EMAIL PROTECTED] wrote:
 
   That's exactly what I was thinking about, but
 your
  hanoi_shower only
   handles list of exactly one action, but you have
  to handle longer lists,
   too. This could be done with explicit recursion
  
  This seems to be a common pitfall for Haskell
  newcomers: mistaking
  a single-element list pattern (such as [x]) for a
  pattern that iterates
  over every element in the list.
  I can't seem to find a page with a list of common
  pitfalls and mistakes...
  is there such a thing?
  
  -- 
  Ariel J. Birnbaum
  ___
  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] Re: Embedding newlines into a string?

2008-04-15 Thread Tillmann Rendel

Benjamin L. Russel wrote:

hanoi_shower ((a, b) : moves)
| null moves = ...
| otherwise == ...


Luke Palmer wrote:

More idiomatic pedantry:  the way you will see most Haskellers write
this style of function is by pattern matching rather than guards:

hanoi_shower [] = ...
hanoi_shower ((a,b):moves) = ...


These two versions are semantically different! Benjamin's versions works 
for lists of length 1 or more, Luke's version works for lists of length 
0 or more.


Luke's version looks like a typical Haskell solution, which would be 
expressed in lispy syntax like this:


(define hanoi_shower (lambda (xs)
  (cond ((null xs) (...))
(true, (let ((a, (first (first xs)))
 (b, (rest (first xs)))
 (moves, (rest xs)))
   (...)

The pattern matching in Haskell takes care of both the cond and the let, 
there's no need for guards or to actually call null or any selector 
functions. A nice exercise may be to implement the map function using 
primitive recursion.


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


Re: [Haskell-cafe] Re: Embedding newlines into a string?

2008-04-15 Thread Benjamin L. Russell
Ok; I rewrote my recursive version of hanoi,
preserving my semantics (i.e., working for lists of
length 1 or more, rather than 0 or more, to start
with) in a more Haskell-idiomatic manner; viz:

hanoi_general_recursive.hs:

hanoi :: a - a - a - Int - [(a, a)]
hanoi source using dest n
| n == 1 = [(source, dest)]
| otherwise = hanoi source dest using (n-1) 
  ++ hanoi source using dest 1
 ++ hanoi using source dest
(n-1)

hanoi_shower :: Show a = [(a, a)] - String
hanoi_shower [(a, b)] = unlines [Move  ++ show a ++
 to ++ show b ++ .]
hanoi_shower ((a, b):moves) = unlines [Move  ++ show
a ++  to ++ show b ++ .] ++ hanoi_shower moves

(I wanted to start out with lists of length 1 as a
base case before extending the base case to lists of
length 0 because Luke Palmer had already solved it for
0, and I didn't want just to copy his solution--I
can't learn anything if I just do that.)

In WinHugs:

Main :load hanoi_general_recursive.hs
Main putStr (hanoi_shower (hanoi 'a' 'b' 'c' 2))
Move 'a' to 'b'.
Move 'a' to 'c'.
Move 'b' to 'c'.

Main putStr (hanoi_shower (hanoi 'a' 'b' 'c' 1))
Move 'a' to 'c'.

Main putStr (hanoi_shower (hanoi 1 2 3 2))
Move 1 to 2.
Move 1 to 3.
Move 2 to 3.

Main putStr (hanoi_shower (hanoi 1 2 3 1))
Move 1 to 3.


Ok; it works now.

Now that I have successfully created a recursive
version that preserves my original semantics, it is
time to extend the base case to handle lists of length
0.

(Notice that I added a base case of n == 0 to hanoi
itself as well, in addition to hanoi_shower; leaving
this out in hanoi results in an error of ERROR - C
stack overflow on an argument of n == 0 discs:)

hanoi_general_recursive_base_0.hs:

hanoi :: a - a - a - Int - [(a, a)]
hanoi source using dest n
| n == 0 = []
| n == 1 = [(source, dest)]
| otherwise = hanoi source dest using (n-1) 
  ++ hanoi source using dest 1
 ++ hanoi using source dest
(n-1)

hanoi_shower :: Show a = [(a, a)] - String
hanoi_shower [] = 
hanoi_shower ((a, b):moves) = unlines [Move  ++ show
a ++  to ++ show b ++ .] ++ hanoi_shower moves

Now, let's sit back and watch the fun in WinHugs:

Main :load hanoi_general_recursive_base_0.hs
Main putStr (hanoi_shower (hanoi 'a' 'b' 'c' 2))
Move 'a' to 'b'.
Move 'a' to 'c'.
Move 'b' to 'c'.

Main putStr (hanoi_shower (hanoi 'a' 'b' 'c' 0))

Main putStr (hanoi_shower (hanoi 1 2 3 2))
Move 1 to 2.
Move 1 to 3.
Move 2 to 3.

Main putStr (hanoi_shower (hanoi 1 2 3 0))


Great!

Just for reference, here's the code for the other
versions for comparison:

hanoi_general_list_comprehension_unwords.hs [Note:
This version adds an extra space before the final '.'
on each line.]:

hanoi :: a - a - a - Int - [(a, a)]
hanoi source using dest n
| n == 1 = [(source, dest)]
| otherwise = hanoi source dest using (n-1) 
  ++ hanoi source using dest 1
 ++ hanoi using source dest
(n-1)

hanoi_shower :: Show a = [(a, a)] - String
hanoi_shower moves = unlines [unwords [Move, show a,
to, show b, .] | (a, b) - moves]

--

hanoi_general_list_comprehension_unlines.hs:

hanoi :: a - a - a - Int - [(a, a)]
hanoi source using dest n
| n == 1 = [(source, dest)]
| otherwise = hanoi source dest using (n-1) 
  ++ hanoi source using dest 1
 ++ hanoi using source dest
(n-1)

hanoi_shower :: Show a = [(a, a)] - String
hanoi_shower moves = unlines [Move  ++ show a ++ 
to ++ show b ++ . | (a, b) - moves]

--
hanoi_general_map_unlines.hs:

hanoi :: a - a - a - Int - [(a, a)]
hanoi source using dest n
| n == 1 = [(source, dest)]
| otherwise = hanoi source dest using (n-1) 
  ++ hanoi source using dest 1
 ++ hanoi using source dest
(n-1)

hanoi_shower :: Show a = [(a, a)] - String
hanoi_shower moves = unlines (map move moves)
 where move (a, b) = Move  ++
show a ++  to ++ show b ++ .

--
hanoi_general_recursive.hs [Note: This version only
works for lists of length 1 or more.]:

hanoi :: a - a - a - Int - [(a, a)]
hanoi source using dest n
| n == 1 = [(source, dest)]
| otherwise = hanoi source dest using (n-1) 
  ++ hanoi source using dest 1
 ++ hanoi using source dest
(n-1)

hanoi_shower :: Show a = [(a, a)] - String
hanoi_shower [(a, b)] = unlines [Move  ++ show a ++
 to ++ show b ++ .]
hanoi_shower ((a, b):moves) = unlines [Move  ++ show
a ++  to ++ show b ++ .] ++ hanoi_shower moves

--
hanoi_general_recursive_base_0.hs [Note: This program
is just the program contained in the file
hanoi_general_recursive.hs, but extended to process
lists of length 0 or more.]:

hanoi :: a - a - a - Int - [(a, a)]
hanoi source using dest n
| n == 0 = []
| n == 1 = [(source, dest)]
| otherwise = hanoi source dest using (n-1) 
  ++ hanoi source using dest 1
 ++ hanoi using source dest
(n-1)


[Haskell-cafe] Re: Embedding newlines into a string?

2008-04-14 Thread Tillmann Rendel

Benjamin L. Russell wrote:

but got stuck on outputting newlines as part of the string;


quoting is done by the show function in Haskell, so you have to take 
care to avoid calling show. your code calls show at two positions:

(1) when you insert the newline into the string
(2) when you output the string

with respect to (1):

you use (show '\n') to create a newline-only string, which produces a 
machine-readable (!) textual representation of '\n'. try the difference 
between


   '\n'

and

   show '\n'

to see what I mean. instead of using (show '\n'), you should simply use 
\n to encode the string of length 1 containing a newline character.


with respect to (2):

the type of your top-level expression is String, which is automatically 
print'ed by the interpreter. but print x = putStrLn (show x), so there 
is another call to show at this point. to avoid this call, write an IO 
action yourself. try the difference between


  putStrLn (hanoi ...)

and

  print (hanoi ...)

to see what I mean.

Last, but not least, I would like to point out a different aproach to 
multiline output which is often used by Haskell programmers: The worker 
functions in this aproach produces a list of strings, which is joined 
together with newlines by the unlines function. In your case:


  hanoi_helper :: ... - [String]
| ... = [Move  ++ ...]
| otherwise = hanoi_helper ... ++ hanoi_helper ...

  hanoi n = hanoi_helper 'a' 'b' 'c' n

and in the interpreter one of these:

   hanoi 2 -- outputs a list
   mapM_ putStrLn (hanoi 2) -- outputs each move in a new line
   putStrLn (unlines (hanoi 2)) -- same as previous line

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


Re: [Haskell-cafe] Re: Embedding newlines into a string?

2008-04-14 Thread Benjamin L. Russell
Ok; much better.  Here's my new type signature and
definition:

hanoi.hs:
hanoi :: Int - IO ()
hanoi n = mapM_ putStrLn (hanoi_helper 'a' 'b' 'c' n)
  
hanoi_helper :: Char - Char - Char - Int -
[String]
hanoi_helper source using dest n
| n == 1 = [Move  ++ show source ++  to  ++
show dest ++ .]
| otherwise = hanoi_helper source dest using (n-1)

  ++ hanoi_helper source using dest 1
 ++ hanoi_helper using source
dest (n-1)

Then in WinHugs (Version Sep 2006):

Hugs :load hanoi.hs
Main hanoi 2
Move 'a' to 'b'.
Move 'a' to 'c'.
Move 'b' to 'c'.

Great!

One minor question:  I tried out both of your
following suggestions:

 mapM_ putStrLn (hanoi 2) -- outputs each move
 in a new line
 putStrLn (unlines (hanoi 2)) -- same as
 previous line

and discovered that putStrLn with unlines (the lower
option) in fact generates one extra blank line at the
end.  Just curious as to why

Benjamin L. Russell

--- Tillmann Rendel [EMAIL PROTECTED] wrote:

 Benjamin L. Russell wrote:
  but got stuck on outputting newlines as part of
 the string;
 
 quoting is done by the show function in Haskell, so
 you have to take 
 care to avoid calling show. your code calls show at
 two positions:
 (1) when you insert the newline into the string
 (2) when you output the string
 
 with respect to (1):
 
 you use (show '\n') to create a newline-only string,
 which produces a 
 machine-readable (!) textual representation of '\n'.
 try the difference 
 between
 
 '\n'
 
 and
 
 show '\n'
 
 to see what I mean. instead of using (show '\n'),
 you should simply use 
 \n to encode the string of length 1 containing a
 newline character.
 
 with respect to (2):
 
 the type of your top-level expression is String,
 which is automatically 
 print'ed by the interpreter. but print x = putStrLn
 (show x), so there 
 is another call to show at this point. to avoid this
 call, write an IO 
 action yourself. try the difference between
 
putStrLn (hanoi ...)
 
 and
 
print (hanoi ...)
 
 to see what I mean.
 
 Last, but not least, I would like to point out a
 different aproach to 
 multiline output which is often used by Haskell
 programmers: The worker 
 functions in this aproach produces a list of
 strings, which is joined 
 together with newlines by the unlines function. In
 your case:
 
hanoi_helper :: ... - [String]
  | ... = [Move  ++ ...]
  | otherwise = hanoi_helper ... ++ hanoi_helper
 ...
 
hanoi n = hanoi_helper 'a' 'b' 'c' n
 
 and in the interpreter one of these:
 
 hanoi 2 -- outputs a list
 mapM_ putStrLn (hanoi 2) -- outputs each move
 in a new line
 putStrLn (unlines (hanoi 2)) -- same as
 previous line
 
 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


Re: [Haskell-cafe] Re: Embedding newlines into a string?

2008-04-14 Thread Neil Mitchell
Hi

   mapM_ putStrLn (hanoi 2) -- outputs each move
   in a new line
   putStrLn (unlines (hanoi 2)) -- same as
   previous line

putStr (unlines (hanoi 2))

is what you want. Unlines puts a trailing new line at the end of every
line, including the final one. putStrLn puts an additional trailing
new line, so you get 2 at the end.

mapM_ putStrLn == putStr . unlines

Thanks

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


Re: [Haskell-cafe] Re: Embedding newlines into a string?

2008-04-14 Thread Tillmann Rendel

Benjamin L. Russell wrote:

Ok; much better.  Here's my new type signature and
definition:

hanoi :: Int - IO ()   
hanoi_helper :: Char - Char - Char - Int - [String]


If you want, you can separate the algorithm and the output processing 
even more by providing three functions of these types:


hanoi :: Int - [(Char, Char)]
hanoi_helper :: Char - Char - Char - Int - [(Char, Char)]
hanoi_shower :: [(Char, Char)] - String

and at the interpreter level:

   putStr (hanoi_shower (hanoi 2))

added value: you can easily use the output of hanoi for automated 
processing (e.g. testing, controlling a robot, producing an animation, 
counting the number of steps).


You can go one step further if you consider that towers don't have to be 
named by single characters, but can be named by everything:


hanoi :: a - a - a - Int - [(a, a)]
hanoi_helper :: a - a - a - Int - [(a, a)]
hanoi_shower :: Show a = [(a, a)] - String

now you can use

   putStr (hanoi_shower (hanoi 'a' 'b' 'c' 2))

to get the same result as above, but you are also allowed to write

   putStr (hanoi_shower (hanoi 1 2 3 2))

if you want to use numeric tower names.

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


Re: [Haskell-cafe] Re: Embedding newlines into a string?

2008-04-14 Thread Neil Mitchell
Hi

  mapM_ putStrLn == putStr . unlines
 

  I'm wondering which (==) you mean here ;)

Expression equality, defined by:

instance (Arbitrary a, Eq b) = Eq (a - b) where
f == g = forall x :: a, f x == g x

Using QuickCheck to generate the values, and an Eq over IO (), which
can be defined using the IO test modelling thing at last years Haskell
Workshop.

There are answers to all these things, even if Haskell can't express
all of them quite like this :)

Thanks

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


Re: [Haskell-cafe] Re: Embedding newlines into a string?

2008-04-14 Thread Tillmann Rendel

Neil Mitchell wrote:

Unlines puts a trailing new line at the end of every
line, including the final one. putStrLn puts an additional trailing
new line, so you get 2 at the end.


Thanks for that clarification.


mapM_ putStrLn == putStr . unlines


I'm wondering which (==) you mean here ;)

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


Re: [Haskell-cafe] Re: Embedding newlines into a string?

2008-04-14 Thread Benjamin L. Russell
Wow, that's very general.  So you want to divide hanoi
into a main function, a helper function, and a display
function.

I tried it out, and got this far so far:

hanoi :: a - a - a - Int - [(a, a)]
hanoi a b c n = hanoi_helper a b c n
  
hanoi_helper :: a - a - a - Int - [(a, a)]
hanoi_helper source using dest n
| n == 1 = [(source, dest)]
| otherwise = hanoi_helper source dest using (n-1)

  ++ hanoi_helper source using dest 1
 ++ hanoi_helper using source
dest (n-1)

hanoi_shower :: Show a = [(a, a)] - String
hanoi_shower [(a, b)] = Move  ++ show a ++  to  ++
show b ++ .

However, when I tried to run the code in WinHugs, this
is what I got:

Hugs :load hanoi_general.hs
Main putStr (hanoi_shower (hanoi 'a' 'b' 'c' 2))

Program error: pattern match failure: hanoi_shower
[('a','b'),('a','c')] ++ ([] ++ hanoi_helper 'b' 'a'
'c' (2 - 1))

There seems to be a bug in hanoi_shower.

I'm still trying to debug hanoi_shower, but I need to
stop for today and continue on this tomorrow.

Thanks for your help so far!  Perhaps I can get this
general version fully working tomorrow.

Benjamin L. Russell

--- Tillmann Rendel [EMAIL PROTECTED] wrote:

 Benjamin L. Russell wrote:
  Ok; much better.  Here's my new type signature and
  definition:
  
  hanoi :: Int - IO ()   
  hanoi_helper :: Char - Char - Char - Int -
 [String]
 
 If you want, you can separate the algorithm and the
 output processing 
 even more by providing three functions of these
 types:
 
 hanoi :: Int - [(Char, Char)]
 hanoi_helper :: Char - Char - Char - Int -
 [(Char, Char)]
 hanoi_shower :: [(Char, Char)] - String
 
 and at the interpreter level:
 
 putStr (hanoi_shower (hanoi 2))
 
 added value: you can easily use the output of hanoi
 for automated 
 processing (e.g. testing, controlling a robot,
 producing an animation, 
 counting the number of steps).
 
 You can go one step further if you consider that
 towers don't have to be 
 named by single characters, but can be named by
 everything:
 
 hanoi :: a - a - a - Int - [(a, a)]
 hanoi_helper :: a - a - a - Int - [(a, a)]
 hanoi_shower :: Show a = [(a, a)] - String
 
 now you can use
 
 putStr (hanoi_shower (hanoi 'a' 'b' 'c' 2))
 
 to get the same result as above, but you are also
 allowed to write
 
 putStr (hanoi_shower (hanoi 1 2 3 2))
 
 if you want to use numeric tower names.
 
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


Re: [Haskell-cafe] Re: Embedding newlines into a string?

2008-04-14 Thread Abhay Parvate
Yes, they are. That's what perhaps Neil Mitchell means by

mapM_ putStrLn == putStr . unlines

And whether the trailing newline is to be called the last blank line depends
upon the convention; The string that is output in both the cases contains a
single newline character. Are you calling that a blank line at end?

And I actually meant to reply to haskell-cafe as well; omitted haskell-cafe
by mistake. Anyway, you got the same answer from two people! This time I am
including haskell-cafe in the recipients.

Regards,
Abhay

On Mon, Apr 14, 2008 at 4:05 PM, Benjamin L. Russell [EMAIL PROTECTED]
wrote:

 Abhay Parvate,

 Thank you; that answered my question.

 Then, the following two lines of code should be
 equivalent:

 In hanoi.hs:
 hanoi n = mapM_ putStrLn (hanoi_helper 'a' 'b' 'c' n)

 In hanoi_unlines.hs:
 hanoi n = putStr (unlines(hanoi_helper 'a' 'b' 'c' n))

 I tested them both out on WinHugs (Version Sep 2006);
 they both generated one blank line at the end.

 Benjamin L. Russell

 --- Abhay Parvate [EMAIL PROTECTED] wrote:

  unlines puts newline after each string; putStrLn
  puts newline after the
  given string. As a result, the output contains two
  newlines in the end. You
  can use putStr instead, since the resultant string
  from 'unlines' will have
  a newline at the end.
 
  On Mon, Apr 14, 2008 at 2:12 PM, Benjamin L. Russell
  [EMAIL PROTECTED]
  wrote:
 
   Ok; much better.  Here's my new type signature and
   definition:
  
   hanoi.hs:
   hanoi :: Int - IO ()
   hanoi n = mapM_ putStrLn (hanoi_helper 'a' 'b' 'c'
  n)
  
   hanoi_helper :: Char - Char - Char - Int -
   [String]
   hanoi_helper source using dest n
  | n == 1 = [Move  ++ show source ++  to  ++
   show dest ++ .]
  | otherwise = hanoi_helper source dest using
  (n-1)
  
++ hanoi_helper source using dest
  1
   ++ hanoi_helper using
  source
   dest (n-1)
  
   Then in WinHugs (Version Sep 2006):
  
   Hugs :load hanoi.hs
   Main hanoi 2
   Move 'a' to 'b'.
   Move 'a' to 'c'.
   Move 'b' to 'c'.
  
   Great!
  
   One minor question:  I tried out both of your
   following suggestions:
  
mapM_ putStrLn (hanoi 2) -- outputs each
  move
in a new line
putStrLn (unlines (hanoi 2)) -- same as
previous line
  
   and discovered that putStrLn with unlines (the
  lower
   option) in fact generates one extra blank line at
  the
   end.  Just curious as to why
  
   Benjamin L. Russell
  
   --- Tillmann Rendel [EMAIL PROTECTED] wrote:
  
Benjamin L. Russell wrote:
 but got stuck on outputting newlines as part
  of
the string;
   
quoting is done by the show function in Haskell,
  so
you have to take
care to avoid calling show. your code calls show
  at
two positions:
(1) when you insert the newline into the string
(2) when you output the string
   
with respect to (1):
   
you use (show '\n') to create a newline-only
  string,
which produces a
machine-readable (!) textual representation of
  '\n'.
try the difference
between
   
'\n'
   
and
   
show '\n'
   
to see what I mean. instead of using (show
  '\n'),
you should simply use
\n to encode the string of length 1 containing
  a
newline character.
   
with respect to (2):
   
the type of your top-level expression is String,
which is automatically
print'ed by the interpreter. but print x =
  putStrLn
(show x), so there
is another call to show at this point. to avoid
  this
call, write an IO
action yourself. try the difference between
   
   putStrLn (hanoi ...)
   
and
   
   print (hanoi ...)
   
to see what I mean.
   
Last, but not least, I would like to point out a
different aproach to
multiline output which is often used by Haskell
programmers: The worker
functions in this aproach produces a list of
strings, which is joined
together with newlines by the unlines function.
  In
your case:
   
   hanoi_helper :: ... - [String]
 | ... = [Move  ++ ...]
 | otherwise = hanoi_helper ... ++
  hanoi_helper
...
   
   hanoi n = hanoi_helper 'a' 'b' 'c' n
   
and in the interpreter one of these:
   
hanoi 2 -- outputs a list
mapM_ putStrLn (hanoi 2) -- outputs each
  move
in a new line
putStrLn (unlines (hanoi 2)) -- same as
previous line
   
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] Re: Embedding newlines into a string?

2008-04-14 Thread Brandon S. Allbery KF8NH


On Apr 14, 2008, at 7:51 , Benjamin L. Russell wrote:

hanoi_shower :: Show a = [(a, a)] - String
hanoi_shower [(a, b)] = Move  ++ show a ++  to  ++ show b ++ .


You've just specified via pattern match that hanoi_shower always gets  
a 1-element list.  Is that really what you intended?


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
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] Re: Embedding newlines into a string?

2008-04-14 Thread Neil Mitchell
Hi

   hanoi_shower [] = ...
   hanoi_shower ((a, b) : moves) = ...

  or (preferably) with map

  hanoi_shower moves = unlines (map show_move moves) where
   show_move (a, b) = ...

A nice list comprehension works wonders in these situations:

hanoi_shower moves = unlines [Move  ++ show a ++  to  ++ show b ++
. | (a,b) - moves]

I would personally remove the . from the end, as its a list of
commands, not sentences - but that is personal choice. I'd also use
unwords, as its slightly shorter:

hanoi_shower moves = unlines [unwords [Move, show a, to, show b] |
(a,b) - moves]

Thanks

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


Re: [Haskell-cafe] Re: Embedding newlines into a string?

2008-04-14 Thread Tillmann Rendel

Benjamin L. Russell wrote:

Wow, that's very general.  So you want to divide hanoi
into a main function, a helper function, and a display
function.

I tried it out, and got this far so far:

[...]

hanoi_shower :: Show a = [(a, a)] - String
hanoi_shower [(a, b)] = Move  ++ show a ++  to  ++
show b ++ .


That's exactly what I was thinking about, but your hanoi_shower only
handles list of exactly one action, but you have to handle longer lists,
too. This could be done with explicit recursion

  hanoi_shower [] = ...
  hanoi_shower ((a, b) : moves) = ...

or (preferably) with map

hanoi_shower moves = unlines (map show_move moves) where
  show_move (a, b) = ...

Note the use of unlines again. I decided to use where to introduce a
local binding to avoid cluttering the top-level scope with function names.

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


Re: [Haskell-cafe] Re: Embedding newlines into a string?

2008-04-14 Thread Brent Yorgey

 hanoi :: a - a - a - Int - [(a, a)]
 hanoi a b c n = hanoi_helper a b c n


Note that now hanoi is exactly the same function as hanoi_helper, so you may
as well just get rid of hanoi_helper. =)

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


Re: [Haskell-cafe] Re: Embedding newlines into a string?

2008-04-14 Thread Benjamin L. Russell
Now it works; viz (in response to Brent Yorgey's
suggestion, I have merged hanoi and hanoi_helper):

hanoi_general_list_comprehension_unwords.hs (based on
Neil Mitchell's suggestion, except for the trailing
'.'):

hanoi :: a - a - a - Int - [(a, a)]
hanoi source using dest n
| n == 1 = [(source, dest)]
| otherwise = hanoi source dest using (n-1) 
  ++ hanoi source using dest 1
 ++ hanoi using source dest
(n-1)

hanoi_shower :: Show a = [(a, a)] - String
hanoi_shower moves = unlines [unwords [Move, show a,
to, show b, .] | (a, b) - moves]

Then, in WinHugs:

Main :load
hanoi_general_list_comprehension_unwords.hs
Main putStr (hanoi_shower (hanoi 'a' 'b' 'c' 2))
Move 'a' to 'b' .
Move 'a' to 'c' .
Move 'b' to 'c' .

Main putStr (hanoi_shower (hanoi 1 2 3 2))
Move 1 to 2 .
Move 1 to 3 .
Move 2 to 3 .

Notwithstanding Neil's advice on removing the trailing
'.', which I appreciate, I would still prefer to
retain it, because, in the interests of literate
programming, I would like a sequence of English
sentences as commands acceptable even to an English
teacher.

So, to be pedantic and remove the ' ' before the '.'
at each line:

hanoi_shower portion of
hanoi_general_list_comprehension_unlines.hs (based on
Neil Mitchell's suggestion):

hanoi_shower :: Show a = [(a, a)] - String
hanoi_shower moves = unlines [Move  ++ show a ++ 
to ++ show b ++ . | (a, b) - moves]

Then, in WinHugs:

Main :load
hanoi_general_list_comprehension_unlines.hs
Main putStr (hanoi_shower (hanoi 'a' 'b' 'c' 2))
Move 'a' to 'b'.
Move 'a' to 'c'.
Move 'b' to 'c'.

Main putStr (hanoi_shower (hanoi 1 2 3 2))
Move 1 to 2.
Move 1 to 3.
Move 2 to 3.

Splendid!

Now, just for fun, let's see what other versions also
work:

hanoi_shower portion of hanoi_general_map_unlines.hs
(based on Tillman Rendel's suggestion):

hanoi_shower :: Show a = [(a, a)] - String
hanoi_shower moves = unlines (map move moves)
 where move (a, b) = Move  ++
show a ++  to ++ show b ++ .

Then, in WinHugs:

Main :load hanoi_general_map_unlines.hs
Main putStr (hanoi_shower (hanoi 'a' 'b' 'c' 2))
Move 'a' to 'b'.
Move 'a' to 'c'.
Move 'b' to 'c'.

Main putStr (hanoi_shower (hanoi 1 2 3 2))
Move 1 to 2.
Move 1 to 3.
Move 2 to 3.

Wonderful!  Thanks especially to Neil Mitchell and
Tillman Rendel for their constructive suggestions.

Nevertheless, I'm still working on the recursive
version.  So far, I've gotten this far:

hanoi_shower portion of hanoi_general_recursive.hs
(based on Tillman Rendel's suggestion):

hanoi_shower :: Show a = [(a, a)] - String
hanoi_shower ((a, b) : moves) 
| null moves = Move  ++ show a ++  to ++ show
b ++ .
| otherwise == Move  ++ show a ++  to ++ show
b ++ . ++ hanoi_shower moves

However, in WinHugs, I get the following error:

Hugs :load hanoi_general_recursive.hs
ERROR file:hanoi_general_recursive.hs:11 - Syntax
error in declaration (unexpected `}', possibly due to
bad layout)

I haven't used recursion in Haskell much so far; I've
only used it in Scheme, so I'm not used to it.

I need to go to lunch now, so I'll work on this part
later.  Perhaps I can get it to work after lunch

Benjamin L. Russell

--- Neil Mitchell [EMAIL PROTECTED] wrote:

 Hi
 
hanoi_shower [] = ...
hanoi_shower ((a, b) : moves) = ...
 
   or (preferably) with map
 
   hanoi_shower moves = unlines (map show_move
 moves) where
show_move (a, b) = ...
 
 A nice list comprehension works wonders in these
 situations:
 
 hanoi_shower moves = unlines [Move  ++ show a ++ 
 to  ++ show b ++
 . | (a,b) - moves]
 
 I would personally remove the . from the end, as
 its a list of
 commands, not sentences - but that is personal
 choice. I'd also use
 unwords, as its slightly shorter:
 
 hanoi_shower moves = unlines [unwords [Move, show
 a, to, show b] |
 (a,b) - moves]
 
 Thanks
 
 Neil
 ___
 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] Re: Embedding newlines into a string?

2008-04-14 Thread Brandon S. Allbery KF8NH


On Apr 14, 2008, at 23:45 , Benjamin L. Russell wrote:


hanoi_shower :: Show a = [(a, a)] - String
hanoi_shower ((a, b) : moves)
| null moves = Move  ++ show a ++  to ++ show b ++ .
| otherwise == Move  ++ show a ++  to ++ show b ++ . ++  
hanoi_shower moves


`==' after the `otherwise'?  (I think the error involving `}' is a  
side effect of the single ugliest part of Haskell syntax, which  
specifies the parser inserting `}' as necessary to try to get a parse.)


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
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] Re: Embedding newlines into a string?

2008-04-14 Thread Luke Palmer
On Tue, Apr 15, 2008 at 3:45 AM, Benjamin L. Russell
[EMAIL PROTECTED] wrote:
 hanoi_shower ((a, b) : moves)
 | null moves = Move  ++ show a ++  to ++ show
  b ++ .
 | otherwise == Move  ++ show a ++  to ++ show
  b ++ . ++ hanoi_shower moves

More idiomatic pedantry:  the way you will see most Haskellers write
this style of function is by pattern matching rather than guards:

hanoi_shower [] = 
hanoi_shower ((a,b):moves) = Move  ++ show a ++  to  ++ show b ++
.\n ++ hanoi_shower moves

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