Embedding newlines into a string? [Was: Re: [Haskell-cafe] Separate a string into a list of strings]

2008-04-14 Thread 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:

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 [EMAIL PROTECTED] wrote:

 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 [EMAIL PROTECTED]
 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=headblob;f=/src/compiler98/Util/Text.hs
 
  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 [EMAIL PROTECTED]
 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
 
 

Re: Embedding newlines into a string? [Was: Re: [Haskell-cafe] Separate a string into a list of strings]

2008-04-14 Thread Neil Mitchell
Hi



On Mon, Apr 14, 2008 at 8:22 AM, Benjamin L. Russell
[EMAIL PROTECTED] wrote:
 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Separate a string into a list of strings

2006-06-12 Thread 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


Re: [Haskell-cafe] Separate a string into a list of strings

2006-06-12 Thread J. Garrett Morris

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 [EMAIL PROTECTED] 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




--
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.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Separate a string into a list of strings

2006-06-12 Thread 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=headblob;f=/src/compiler98/Util/Text.hs

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 [EMAIL PROTECTED] 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


Re: [Haskell-cafe] Separate a string into a list of strings

2006-06-12 Thread Clifford Beshers




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




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


Re: [Haskell-cafe] Separate a string into a list of strings

2006-06-12 Thread Brandon Moore

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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Separate a string into a list of strings

2006-06-12 Thread 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 [EMAIL PROTECTED] 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=headblob;f=/src/compiler98/Util/Text.hs

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 [EMAIL PROTECTED] 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


Re: [Haskell-cafe] Separate a string into a list of strings

2006-06-12 Thread Neil Mitchell

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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Separate a string into a list of strings

2006-06-12 Thread Clifford Beshers

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.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe