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

Benjamin L. Russell dekudekuplex at yahoo.com
Wed Apr 16 01:12:48 EDT 2008


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)

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

--

Thanks for all your help!  Thanks especially to  
Tillmann Rendel, Neil Mitchell, and Luke Palmer for
their sample code, to Brandon S. Allbery KF8NH for his
acute questions, to Brent Yorgey for pointing out that
hanoi_helper was superfluous, and to Abhay Parvate for
his discussion of the meaning of Neil Mitchell's
"mapM_ putStrLn == putStr . unlines" (I hope I didn't
miss anybody).

Next step: to figure out how to write hanoi in CPS. 
More on this later....

Benjamin L. Russell

--- Tillmann Rendel <rendel at daimi.au.dk> wrote:

> 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 



More information about the Haskell-Cafe mailing list