Separate a string into a list of strings

Hi all, I want to write a function to separate a string into a list of strings separated by commas. Example: separate :: String -> [String] separate "Haskell, Haskell, and Haskell" = ["Haskell", "Haskell", "and Haskell"] If anyone has some ideas, please share with me. Thanks. S.

Off the top of my head:
separate :: String -> [String]
separate [] = []
separate s =
case break (',' ==) s of
(s,[]) -> [s]
(s,',':s') -> s : separate s'
_ -> error "how did we get here?"
There is at least one cunning rewriting with foldl, I think, but I
think this version is clearer.
/g
On 6/12/06, Sara Kenedy
Hi all,
I want to write a function to separate a string into a list of strings separated by commas.
Example: separate :: String -> [String]
separate "Haskell, Haskell, and Haskell" = ["Haskell", "Haskell", "and Haskell"]
If anyone has some ideas, please share with me. Thanks.
S. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- We have lingered in the chambers of the sea By sea-girls wreathed with seaweed red and brown Till human voices wake us, and we drown.

Well, I couldn't resist the puzzle. Here are solutions using foldr and unfoldr. Don't know if they are cunning or not, but they were kind of fun. import Data.List splitByElem e xs = unfoldr f xs where f s = case break (e ==) s of ("",_) -> Nothing (a,b) -> Just (a, drop 1 b) splitByElem1 e xs = foldr f [[]] xs where f a b = if a == e then [] : b else (a : head b) : (tail b) J. Garrett Morris wrote:
There is at least one cunning rewriting with foldl, I think, but I think this version is clearer.
/g
On 6/12/06, Sara Kenedy
wrote: Hi all,
I want to write a function to separate a string into a list of strings separated by commas.
Example: separate :: String -> [String]
separate "Haskell, Haskell, and Haskell" = ["Haskell", "Haskell", "and Haskell"]
If anyone has some ideas, please share with me. Thanks.
S. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi,
I tend to use the module TextUtil (or Util.Text) from Yhc for these
kind of string manipulations:
http://www-users.cs.york.ac.uk/~malcolm/cgi-bin/darcsweb.cgi?r=yhc;a=headblo...
separate = splitList ","
I am currently thinking about making this module into a standalone
library with some other useful functions, if people have any opinions
on this then please let me know.
Thanks
Neil
On 6/12/06, Sara Kenedy
Hi all,
I want to write a function to separate a string into a list of strings separated by commas.
Example: separate :: String -> [String]
separate "Haskell, Haskell, and Haskell" = ["Haskell", "Haskell", "and Haskell"]
If anyone has some ideas, please share with me. Thanks.
S. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Funny. I have a module called Useful.hs with some of these same sorts
of functions. (coming from Python where I used .split(',') and
.replace('\r', '') and such a lot):
------------------
module Useful where
import List ( intersperse, tails )
import Numeric ( readHex )
hex2num :: (Num a) => String -> a
hex2num s = let (result, _):_ = readHex s in result
toEnv s = map tuple (split ';' s)
tuple :: String -> (String, String)
tuple line = case split '=' line of
a:b:_ -> (a,b)
a:_ -> (a,"")
_ -> ("","") -- not good, probably won't happen for my typical usage...
split :: Char -> String -> [String]
split _ "" = []
split c s = let (l, s') = break (== c) s
in l : case s' of
[] -> []
(_:s'') -> split c s''
beginsWith [] [] = True
beginsWith _ [] = True
beginsWith [] _ = False
beginsWith (a:aa) (b:bb)
| a == b = aa `beginsWith` bb
| otherwise = False
dropping [] [] = []
dropping [] _ = []
dropping x [] = x
dropping s@(a:aa) (b:bb) | a == b = dropping aa bb
| otherwise = s
-- replace all occurrences of 'this' with 'that' in the string 'str'
-- like Python replace
replace _ _ [] = []
replace this that str
| str `beginsWith` this = let after = (str `dropping` this)
in that ++ replace this that after
| otherwise =
let x:xs = str
in x : replace this that xs
eat s = replace s ""
-- sometimes newlines get out of hand on the end of form POST submissions,
-- so trim all the end newlines and add a single newline
fixEndingNewlines = reverse . ('\n':) . dropWhile (=='\n') . reverse .
filter (/= '\r')
endsWith a b = beginsWith (reverse a) (reverse b)
a `contains` b = any (`beginsWith` b) $ tails a
------------------
Jared.
On 6/12/06, Neil Mitchell
Hi,
I tend to use the module TextUtil (or Util.Text) from Yhc for these kind of string manipulations:
http://www-users.cs.york.ac.uk/~malcolm/cgi-bin/darcsweb.cgi?r=yhc;a=headblo...
separate = splitList ","
I am currently thinking about making this module into a standalone library with some other useful functions, if people have any opinions on this then please let me know.
Thanks
Neil
On 6/12/06, Sara Kenedy
wrote: Hi all,
I want to write a function to separate a string into a list of strings separated by commas.
Example: separate :: String -> [String]
separate "Haskell, Haskell, and Haskell" = ["Haskell", "Haskell", "and Haskell"]
If anyone has some ideas, please share with me. Thanks.
S. _______________________________________________ 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
-- http://www.updike.org/~jared/ reverse ")-:"

Hi
beginsWith [] [] = True beginsWith _ [] = True beginsWith [] _ = False beginsWith (a:aa) (b:bb) | a == b = aa `beginsWith` bb | otherwise = False
I used to have this in my library then I discovered isPrefixOf :) (or flip isPrefixOf, I think in this case)
endsWith a b = beginsWith (reverse a) (reverse b) ditto, isSuffixOf
Thanks Neil

"Jared Updike"
On 6/12/06, Neil Mitchell
wrote:
I tend to use the module TextUtil (or Util.Text) from Yhc for these kind of string manipulations:
Funny. I have a module called Useful.hs with some of these same sorts of functions. (coming from Python where I used .split(',') and .replace('\r', '') and such a lot):
Clifford Beshers writes:
Here is a solution using the Posix regex module.
In addition, there are similar things in John Goerzen's MissingH, and in FPS. It'd be nice if the Data.List interface included these. Seems there is a two-d matrix, one is the split criterion (matching element, number of elements, boolean function on elements), the other is the return type (split off one (-> ([a],[a])) or split up the whole string (-> [[a]])). Arbitrarily¹ naming the former 'split' and the latter 'break', you could have something like: split :: a -> [a] -> ([a],[a]) splitAt :: Int -> [a] -> ([a],[a]) splitWhen :: (a -> Bool) -> [a] -> ([a],[a]) break :: a -> [a] -> [[a]] breakAt :: Int -> [a] -> [[a]] breakWhen :: (a -> Bool) -> [a] -> [[a]] -k ¹ Well, perhaps not quite, it seems more natural to me to 'split in two' and 'break into pieces'. -- If I haven't seen further, it is by standing in the footprints of giants

A friend and I were working on a Haskell version of
Towers of Hanoi yesterday, and I tried writing out the
program today, but got stuck on outputting newlines as
part of the string; viz:
hanoi :: Int -> String
hanoi n = hanoi_helper 'a' 'b' 'c' n
hanoi_helper :: Char -> Char -> Char -> Int -> String
hanoi_helper source using dest n
| n == 1 = putStrLn "Move " ++ show source ++ " to
" ++ show dest ++ "." ++ show '\n'
| otherwise = hanoi_helper source dest using (n-1)
++ hanoi_helper source using dest 1
++ hanoi_helper using source
dest (n-1)
The problem is that the newlines ('\n') get embedded
as escaped newlines into the output string, instead of
as newlines.
E.g.,
Hugs> :load hanoi.hs
Main> hanoi 2
"Move 'a' to 'b'.'\\n'Move 'a' to 'c'.'\\n'Move 'b' to
'c'.'\\n'"
Instead, what I want is the following:
Hugs> :load hanoi.hs
Main> hanoi 2
"Move 'a' to 'b'.
Move 'a' to 'c'.
Move 'b' to 'c'.
"
However, when I try to use putStrLn to avoid this
problem, as follows:
| n == 1 = putStrLn "Move " ++ show source ++ " to
" ++ show dest ++ "." ++ show '\n'
the compiler generates the following error:
ERROR file:hanoi.hs:6 - Type error in application
*** Expression : putStrLn "Move " ++ show source
++ " to " ++ show dest ++ "." ++ show '\n'
*** Term : putStrLn "Move "
*** Type : IO ()
*** Does not match : [Char]
Simply changing the type signature does not solve this
problem.
I searched through the past messages on this list, and
came up with the message below, but simply quoting the
newlines as '\n' doesn't seem to help.
Does anybody know a way to embed a newline into a
string as output of type String of a function so that
the newline characters are not escaped?
Benjamin L. Russell
--- Jared Updike
Funny. I have a module called Useful.hs with some of these same sorts of functions. (coming from Python where I used .split(',') and .replace('\r', '') and such a lot):
------------------ module Useful where
import List ( intersperse, tails ) import Numeric ( readHex )
hex2num :: (Num a) => String -> a hex2num s = let (result, _):_ = readHex s in result
toEnv s = map tuple (split ';' s)
tuple :: String -> (String, String) tuple line = case split '=' line of a:b:_ -> (a,b) a:_ -> (a,"") _ -> ("","") -- not good, probably won't happen for my typical usage...
split :: Char -> String -> [String] split _ "" = [] split c s = let (l, s') = break (== c) s in l : case s' of [] -> [] (_:s'') -> split c s''
beginsWith [] [] = True beginsWith _ [] = True beginsWith [] _ = False beginsWith (a:aa) (b:bb) | a == b = aa `beginsWith` bb | otherwise = False
dropping [] [] = [] dropping [] _ = [] dropping x [] = x dropping s@(a:aa) (b:bb) | a == b = dropping aa bb | otherwise = s
-- replace all occurrences of 'this' with 'that' in the string 'str' -- like Python replace replace _ _ [] = [] replace this that str | str `beginsWith` this = let after = (str `dropping` this) in that ++ replace this that after | otherwise = let x:xs = str in x : replace this that xs
eat s = replace s ""
-- sometimes newlines get out of hand on the end of form POST submissions, -- so trim all the end newlines and add a single newline fixEndingNewlines = reverse . ('\n':) . dropWhile (=='\n') . reverse . filter (/= '\r')
endsWith a b = beginsWith (reverse a) (reverse b)
a `contains` b = any (`beginsWith` b) $ tails a ------------------
Jared.
On 6/12/06, Neil Mitchell
wrote: Hi,
I tend to use the module TextUtil (or Util.Text) from Yhc for these kind of string manipulations:
http://www-users.cs.york.ac.uk/~malcolm/cgi-bin/darcsweb.cgi?r=yhc;a=headblo...
separate = splitList ","
I am currently thinking about making this module
library with some other useful functions, if
into a standalone people have any opinions
on this then please let me know.
Thanks
Neil
On 6/12/06, Sara Kenedy
wrote: Hi all,
I want to write a function to separate a string into a list of strings separated by commas.
Example: separate :: String -> [String]
separate "Haskell, Haskell, and Haskell" = ["Haskell", "Haskell", "and Haskell"]
If anyone has some ideas, please share with me. Thanks.
S. _______________________________________________ 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
-- http://www.updike.org/~jared/ reverse ")-:" _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi
On Mon, Apr 14, 2008 at 8:22 AM, Benjamin L. Russell
A friend and I were working on a Haskell version of Towers of Hanoi yesterday, and I tried writing out the program today, but got stuck on outputting newlines as part of the string; viz:
| n == 1 = putStrLn ("Move " ++ show source ++ " to " ++ show dest ++ "." ++ show '\n')
show '\n' = "\\n" "\n" == "\n" Therefore:
| n == 1 = putStrLn ("Move " ++ show source ++ " to " ++ show dest ++ "." ++ "\n")
Note that you need the brackets, an in general don't call show on a String or a Char. Thanks Neil

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

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
but got stuck on outputting newlines as part of
Benjamin L. Russell wrote: 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

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

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

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

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

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

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] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

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

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

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

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] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On Tue, Apr 15, 2008 at 3:45 AM, Benjamin L. Russell
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

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

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

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

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"
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

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...
Hope this helps....
Benjamin L. Russell
--- "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"
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

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

Ariel,
--- "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.
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

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

Ariel,
--- "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.
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

Hello Neil, Tuesday, June 13, 2006, 2:55:42 AM, you wrote:
I tend to use the module TextUtil (or Util.Text) from Yhc for these kind of string manipulations: I am currently thinking about making this module into a standalone library with some other useful functions, if people have any opinions on this then please let me know.
having good Strings library is a MUST. it required everyday and every large enough program contains such internal modules. moreover, such module is absolute need to write scripts in Haskell, and i think it should be included in std hierarchical libs. i already had the idea of starting such module so if you can do public repository for it - it will be even better -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Sara Kenedy wrote:
Hi all,
I want to write a function to separate a string into a list of strings separated by commas.
Example: separate :: String -> [String]
separate "Haskell, Haskell, and Haskell" = ["Haskell", "Haskell", "and Haskell"]
If anyone has some ideas, please share with me. Thanks. Here is a solution using the Posix regex module.
Prelude Text.Regex> splitRegex (mkRegex "[ \t]*,[ \t]*") "Haskell, Haskell, and Haskell" ["Haskell","Haskell","and Haskell"] This form should work regardless of locale, but appears to be broken, although I expect this is either my fault or that of the underlying Posix library: Prelude Text.Regex> splitRegex (mkRegex "[:space:]*,[:space:]*") "Haskell, Haskell, and Haskell" ["Haskell"," Haskell"," and Haskell"]

Clifford Beshers wrote:
Sara Kenedy wrote:
Hi all,
I want to write a function to separate a string into a list of strings separated by commas.
Example: separate :: String -> [String]
separate "Haskell, Haskell, and Haskell" = ["Haskell", "Haskell", "and Haskell"]
If anyone has some ideas, please share with me. Thanks.
Here is a solution using the Posix regex module.
Prelude Text.Regex> splitRegex (mkRegex "[ \t]*,[ \t]*") "Haskell, Haskell, and Haskell" ["Haskell","Haskell","and Haskell"]
This form should work regardless of locale, but appears to be broken, although I expect this is either my fault or that of the underlying Posix library:
Prelude Text.Regex> splitRegex (mkRegex "[:space:]*,[:space:]*") "Haskell, Haskell, and Haskell" ["Haskell"," Haskell"," and Haskell"]
Going by man grep, those [:foo:] classes are only special inside a character class, otherwise [:space:]* = [aceps:]*. Prelude Text.Regex> splitRegex (mkRegex "[[:space:]]*,[[:space:]]*") "Haskell, Haskell, and Haskell" ["Haskell","Haskell","and Haskell"] Brandon

Brandon Moore wrote:
Going by man grep, those [:foo:] classes are only special inside a character class, otherwise [:space:]* = [aceps:]*.
Prelude Text.Regex> splitRegex (mkRegex "[[:space:]]*,[[:space:]]*") "Haskell, Haskell, and Haskell" ["Haskell","Haskell","and Haskell"]
The smart money was on user error. Thanks.
participants (14)
-
Ariel J. Birnbaum
-
Benjamin L. Russell
-
Brandon Moore
-
Brandon S. Allbery KF8NH
-
Brent Yorgey
-
Bulat Ziganshin
-
Clifford Beshers
-
J. Garrett Morris
-
Jared Updike
-
Ketil Malde
-
Luke Palmer
-
Neil Mitchell
-
Sara Kenedy
-
Tillmann Rendel