
Hi Everyone My first post to the mailing list is a cry for help. Apologies for that. I've seen an example of how this is done in the archives but I'm afraid I'm a bit more behind than the person who seemed to understand the answer so if someone could help me?? The problem is this: I've show(n) a particular data type and it shows up as: [([2,6],"British"),([1],"Charles"),([1,8],"Clarke"),([2,6],"Council"),([2],"Edinburgh"),([1],"Education"),([4],"Increasingly")] What I want to do is format that nicely into a table. The best way of doing (I thought) was to: Remove the first "[(" and final ")]" Then replace "),(" with a newline(\n) Which would give: [2,6],"British" [1],"Charles" [1,8],"Clarke" [2,6],"Council" ......etc I get the impression I may find it easier adding newlines earlier on in my program but I thought this may be the easiest way. I'll include all the code for the whole program in case it helps to see where I'm coming from. It takes an input file of text and outputs an index to an output file. My soul question and drive is to lay out the index in a nicely formatted fashion. Any help would be very much appreciated. module TextProc where -- import Prelude hiding (Word) import IO import List type Word = String -- define types type Line = String type Doc = String start :: IO () start = do putStrLn "******** Enter Choice *********" putStrLn "1. Enter Input and Output files" putStrLn "2. Exit" putStrLn "*******************************" choice <- getLine if (choice == "1") then ( do putStrLn "Type input file name:" fileNameI <- getLine text <- readFile fileNameI putStrLn "Type output file name:" fileNameO <- getLine writeFile fileNameO (makeIndex text) ) else ( do return() ) makeIndex :: Doc -> Doc -- changed so output can be written to file makeIndex = show . shorten . -- [([Int], Word)] -> [([Int], Word)] amalgamate . -- [([Int], Word)] -> [([Int], Word)] makeLists . -- [(Int, Word)] -> [([Int], Word)] sortLs . -- [(Int, Word)] -> [(Int, Word)] allNumWords . -- [(Int, Line)] -> [(Int, Word)] numLines . -- [Line] -> [(Int, Line)] splitUp -- Doc -> [Line] splitUp :: Doc -> [Line] splitUp [] = [] splitUp ls = takeWhile (/='\n') ls : -- first line (splitUp . -- split up other line dropWhile (=='\n') . -- delete 1st newLine(s) dropWhile (/='\n')) ls -- other lines numLines :: [Line] -> [(Int, Line)] numLines lines -- list of pairs of = zip [1 .. length lines] lines -- line no. & line splitWords :: Line -> [Word] -- split up lines into words splitWords [] = [] splitWords line = takeWhile isLetter line : -- first word in line (splitWords . -- split other words dropWhile (not.isLetter) . -- delete separators dropWhile isLetter) line -- other words where isLetter ch = ('a' <= ch) && (ch <= 'z') || ('A' <= ch) && (ch <= 'Z') || ('-' == ch) numWords :: (Int, Line) -> [(Int, Word)] -- attach line no. to each word numWords (number, line) = map addLineNum (splitWords line) -- all line pairs where addLineNum word = (number, word) -- a pair allNumWords :: [(Int, Line)] -> [(Int, Word)] allNumWords = concat . map numWords -- doc pairs sortLs :: [(Int, Word)] -> [(Int, Word)] sortLs [ ] = [ ] sortLs (a:x) = sortLs [b | b <- x, compare b a] -- sort 1st half ++ [a] ++ -- 1st in middle sortLs [b | b <- x, compare a b] -- sort 2nd half where compare (n1, w1) (n2, w2) = (w1 < w2) -- 1st word less || (w1 == w2 && n1 < n2) -- check no. makeLists :: [(Int, Word)] -> [([Int], Word)] makeLists = map mk -- all pairs where mk (num, word) = ([num], word) -- list of single no. amalgamate :: [([Int], Word)] -> [([Int], Word)] amalgamate [ ] = [ ] amalgamate [a] = [a] amalgamate ((n1, w1) : (n2, w2) : rest) -- pairs of pairs | w1 /= w2 = (n1, w1) : amalgamate ((n2, w2) : rest) | otherwise = amalgamate ((n1 ++ n2, w1) : rest) -- if words are same grow list of numbers shorten :: [([Int], Word)] -> [([Int], Word)] shorten = filter long -- keep pairs >4 where long (num, word) = length word > 4 -- check word >4

"Douglas" == Douglas Bromley
writes:
Douglas> What I want to do is format that nicely into a table. The Douglas> best way of doing (I thought) was to: Remove the first "[(" Douglas> and final ")]" Then replace "),(" with a newline(\n) Why don't simply write an "output" function which takes your structure (not the result of "show") and output it nicely on the standard output? Sam, puzzled -- Samuel Tardieu -- sam@rfc1149.net -- http://www.rfc1149.net/sam

Douglas Bromley
I've show(n) a particular data type and it shows up as: [([2,6],"British"),([1],"Charles"),([1,8],"Clarke"),([2,6],"Council"),([2],"Edinburgh"),([1],"Education"),([4],"Increasingly")]
Let me guess: type [([Integer],String)]?
What I want to do is format that nicely into a table.
Since you (probably) want one list entry on a line, why not format each entry as a string, and output each string as a line? You may find the function "unlines" to be helpful.
The best way of doing (I thought) was to: Remove the first "[(" and final ")]" Then replace "),(" with a newline(\n)
If you really want to do this (reformat the string), you could perhaps write a function that substitutes a substring for something else, perhaps using "isPrefixOf", "drop" and "take". But this will be a more fragile design than working from the original data strucure. -kzm -- If I haven't seen further, it is by standing in the footprints of giants

To amplify on the other replies you already had, don't use show here:
makeIndex :: Doc -> Doc -- changed so output can be written to file makeIndex = show . shorten . -- [([Int], Word)] -> [([Int], Word)] amalgamate . -- [([Int], Word)] -> [([Int], Word)] makeLists . -- [(Int, Word)] -> [([Int], Word)] sortLs . -- [(Int, Word)] -> [(Int, Word)] allNumWords . -- [(Int, Line)] -> [(Int, Word)] numLines . -- [Line] -> [(Int, Line)] splitUp -- Doc -> [Line]
Instead use, e.g. printastable :: [([Int],Word)] -> String printastable l = concat $ map (\(xs,w) -> (show xs) ++ " " ++ w ++ "\n") l Jules

I'd just like to thank everyone for helping. Its now working great!
I really appreciate your help. I only wish I'd discovered the mailing
list sooner.
All the best.
Doug
On Thu, 9 Dec 2004 10:31:52 +0000, Jules Bean
To amplify on the other replies you already had, don't use show here:
makeIndex :: Doc -> Doc -- changed so output can be written to file makeIndex = show . shorten . -- [([Int], Word)] -> [([Int], Word)] amalgamate . -- [([Int], Word)] -> [([Int], Word)] makeLists . -- [(Int, Word)] -> [([Int], Word)] sortLs . -- [(Int, Word)] -> [(Int, Word)] allNumWords . -- [(Int, Line)] -> [(Int, Word)] numLines . -- [Line] -> [(Int, Line)] splitUp -- Doc -> [Line]
Instead use, e.g.
printastable :: [([Int],Word)] -> String
printastable l = concat $ map (\(xs,w) -> (show xs) ++ " " ++ w ++ "\n") l
Jules

printastable :: [([Int],Word)] -> String
printastable l = concat $ map (\(xs,w) -> (show xs) ++ " " ++ w ++ "\n") l
I'd use [ c | (xs,w) <- l, c <- (show xs) ++ " " ++ w ++ "\n" ] instead -- after all, list comprehensions provide a much nicer syntax for map, filter and concat. -- Thomas

Thomas Johnsson wrote:
printastable :: [([Int],Word)] -> String
printastable l = concat $ map (\(xs,w) -> (show xs) ++ " " ++ w ++ "\n") l
I'd use
[ c | (xs,w) <- l, c <- (show xs) ++ " " ++ w ++ "\n" ]
instead -- after all, list comprehensions provide a much nicer syntax for map, filter and concat.
Or, if you hate append as much as I do: [ c | (xs,w) <- l, cs <- [show xs, " ", w, "\n"], c <- cs ] If you're hard-core, you can turn show into shows and delete a comma... (OK, it's terribly silly in this example, but I do use list comprehensions in this way to avoid concat-ing an already-appended-together list.) -Jan-Willem Maessen
-- Thomas
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Fri, 10 Dec 2004, Thomas Johnsson wrote:
printastable :: [([Int],Word)] -> String
printastable l = concat $ map (\(xs,w) -> (show xs) ++ " " ++ w ++ "\n") l
I'd use
[ c | (xs,w) <- l, c <- (show xs) ++ " " ++ w ++ "\n" ]
instead -- after all, list comprehensions provide a much nicer syntax for map, filter and concat.
I try to stay away from list comprehension because I can't memorize in which order the conditions are processed and I have to introduce new variables. List comprehension means thinking with variables, using 'map' and 'concat' means thinking with functions. Btw. if you want to save characters you can also use 'concatMap': printAsTable = concatMap (\(xs,w) -> show xs ++ " " ++ w ++ "\n") or printAsTable = unlines . map (\(xs,w) -> show xs ++ " " ++ w)

Henning Thielemann wrote:
I try to stay away from list comprehension because I can't memorize in which order the conditions are processed [...]
I remember it as being slowest-changing-to-the-left, just like the positional notation for integers. E.g. [[x,y] | x <- ['1'..'4'], y <- ['0'..'9']] will give you the numbers from 10 to 49 in order (as strings). Another way to remember is that it's the same order as its equivalent using the list monad: do { x <- ['1'..'4']; y <- ['0'..'9']; return [x,y] } -- Ben

printastable :: [([Int],Word)] -> String
printastable l = concat $ map (\(xs,w) -> (show xs) ++ " " ++ w ++ "\n") l
I'd use
[ c | (xs,w) <- l, c <- (show xs) ++ " " ++ w ++ "\n" ]
instead -- after all, list comprehensions provide a much nicer syntax for map, filter and concat.
I try to stay away from list comprehension because I can't memorize in which order the conditions are processed and I have to introduce new variables. [..]
I find it helpful to compare list comprehensions to nested loops & ifs in imperative languages, so that eg [ E | v1 <- E1, pred2, v3 <- E3 ] 'does the same thing as' for( v1 <- E1 ){ if( pred2 ){ for( v3 <- E3){ put-elem-in-resulting-list( E ) } } } -- Thomas

Douglas Bromley
I've show(n) a particular data type and it shows up as: [([2,6],"British"),([1],"Charles"),([1,8],"Clarke"),([2,6],"Council"),([2],"Edinburgh"),([1],"Education"),([4],"Increasingly")]
What I want to do is format that nicely into a table. Which would give: [2,6],"British" [1],"Charles" [1,8],"Clarke" [2,6],"Council" ......etc
makeIndex = show . shorten . -- [([Int], Word)] -> [([Int], Word)]
I'd use unlines . map (\(f,s)->shows f (',':s)) instead of show; it also gets rid of the quotation marks. -- Cheers, Feri.

numLines :: [Line] -> [(Int, Line)] numLines lines -- list of pairs of = zip [1 .. length lines] lines -- line no. & line
zip stops when it reaches the end of the shorter list, so you can just say
zip [1 ..] lines
In fact, most programmers use the infix version of zip, like this:
[1..] `zip` lines
which is nicely readable. (any function can be turned into an infix by surrounding it in `backticks`).
--KW 8-)
--
Keith Wansbrough

Keith Wansbrough wrote:
zip stops when it reaches the end of the shorter list, so you can just say
zip [1 ..] lines
In fact, most programmers use the infix version of zip, like this:
[1..] `zip` lines
which is nicely readable. (any function can be turned into an infix by surrounding it in `backticks`).
And I thought that most programmers used "zipWith", which has to be prefix. Proving that I so rarely want lists of pairs, -Jan-Willem Maessen

And I thought that most programmers used "zipWith", which has to be prefix.
Is this true? Can you not use backticks on a partially applied function? If so, it seems like such a thing would be pretty useful (although I've never actually had occasion to need it, so....) I'll dig out the report and check sometime, but does anyone know for sure that the following wouldn't work? [1..5] `zipWith (+)` [7..]

Robert Dockins
And I thought that most programmers used "zipWith", which has to be prefix.
[1..5] `zipWith (+)` [7..]
You don't have a computer at your end of the internet? :-) Prelude> [1..5] `zipWith (+)` [7..] <interactive>:1: parse error on input `(' Prelude> let zwp = zipWith (+) in [1..5] `zwp` [7..] [8,10,12,14,16] -kzm -- If I haven't seen further, it is by standing in the footprints of giants

Ketil Malde wrote:
Robert Dockins
writes: And I thought that most programmers used "zipWith", which has to be prefix.
[1..5] `zipWith (+)` [7..]
You don't have a computer at your end of the internet? :-)
Yes, but I'm at work, and I try to limit the amount of time I spend on my hobbies while on the clock; thus I have not haskell compilers/interpreters here because otherwise I'd spend all of my time playing around with haskell instead of doing what I'm supposed to ;-) Haskell is a lot more fun than Java.
Prelude> [1..5] `zipWith (+)` [7..] <interactive>:1: parse error on input `(' Prelude> let zwp = zipWith (+) in [1..5] `zwp` [7..] [8,10,12,14,16]
I thought that might be the case. To the haskell gods: is there a technical reason for this or did it just happen?

Robert Dockins
Prelude> [1..5] `zipWith (+)` [7..] <interactive>:1: parse error on input `('
is there a technical reason for this or did it just happen?
If you are asking why general expressions are prohibited between backticks, yes, there is a reason. The expression could be arbitrarily large, so you might have to search many lines to find the closing backtick. But in such a situation, it is surely much more likely that the programmer has simply forgotten to close the ticks around a simple identifier. Just think of the potential for delightfully baffling type error messages that might result! Regards, Malcolm

Malcolm Wallace wrote:
Prelude> [1..5] `zipWith (+)` [7..] <interactive>:1: parse error on input `('
is there a technical reason for this or did it just happen?
If you are asking why general expressions are prohibited between backticks, yes, there is a reason. The expression could be arbitrarily large, so you might have to search many lines to find the closing backtick. But in such a situation, it is surely much more likely that the programmer has simply forgotten to close the ticks around a simple identifier. Just think of the potential for delightfully baffling type error messages that might result!
There's also the issue that you wouldn't be allowed to use backticks
within such an expression, so you would need additional grammar rules
describing expressions which are allowed within backticks.
--
Glynn Clements

On Thu, 9 Dec 2004, Robert Dockins wrote:
And I thought that most programmers used "zipWith", which has to be prefix.
Is this true? Can you not use backticks on a partially applied function? If so, it seems like such a thing would be pretty useful (although I've never actually had occasion to need it, so....) I'll dig out the report and check sometime, but does anyone know for sure that the following wouldn't work?
[1..5] `zipWith (+)` [7..]
Infix operators are syntactic sugar, they are neither necessary nor essential. They can be used to simulate mathematical notation, if one considers that to be more readable, not only because it is more common. I don't think that it is a good idea to extend the infix notation to any functional expression. I also think that one should use backquotes rarely and especially one should not define library functions with their parameters in the "wrong" order just because one expects that the user of the library will stick to the infix notation and slicing (such as (`zip` x)). I hope that it is not true, that most programmers write `zip`. If it is true, I doubt, that this is good style. :-]

On Thu, 09 Dec 2004 10:18:12 -0500, Robert Dockins
And I thought that most programmers used "zipWith", which has to be prefix.
Is this true? Can you not use backticks on a partially applied function? If so, it seems like such a thing would be pretty useful (although I've never actually had occasion to need it, so....) I'll dig out the report and check sometime, but does anyone know for sure that the following wouldn't work?
[1..5] `zipWith (+)` [7..]
It is possible to emulate this behaviour with some operator trickery. See: http://www.haskell.org/pipermail/haskell-cafe/2002-July/003215.html /Josef

On Thu, Dec 09, 2004 at 10:02:39AM -0500, Jan-Willem Maessen - Sun Labs East wrote:
And I thought that most programmers used "zipWith", which has to be prefix.
You can also use zipWith to simulate zipN, for any N (however, the following code uses infix notation): Prelude> let l = words "Haskell is great" Prelude> let zwApply = zipWith ($) Prelude> repeat (,,) `zwApply` [1..] `zwApply` l `zwApply` map length l [(1,"Haskell",7),(2,"is",2),(3,"great",5)] Prelude> map (,,) l `zwApply` [1..] `zwApply` map length l [("Haskell",1,7),("is",2,2),("great",3,5)] I found it useful recently, when I needed zip functions for Trees - this way I didn't have to define functions for 3 trees, 4 trees, and so on. Best regards, Tomasz

Tomasz Zielonka wrote:
On Thu, Dec 09, 2004 at 10:02:39AM -0500, Jan-Willem Maessen - Sun Labs East wrote:
And I thought that most programmers used "zipWith", which has to be prefix.
You can also use zipWith to simulate zipN, for any N (however, the following code uses infix notation):
Prelude> let l = words "Haskell is great" Prelude> let zwApply = zipWith ($) Prelude> repeat (,,) `zwApply` [1..] `zwApply` l `zwApply` map length l [(1,"Haskell",7),(2,"is",2),(3,"great",5)] Prelude> map (,,) l `zwApply` [1..] `zwApply` map length l [("Haskell",1,7),("is",2,2),("great",3,5)]
I found it useful recently, when I needed zip functions for Trees - this way I didn't have to define functions for 3 trees, 4 trees, and so on.
Note also that: repeat f `zwApply` xs = map f xs When cooking up my own collection-y things (including splittable supplies, for example), I generally provide fmap and an equivalent of zwApply (a generic repeat is not quite so simple or useful). It's a nice little idiom, and a recommend it highly. -Jan-Willem Maessen
Best regards, Tomasz _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi Jan-Willem Maessen - Sun Labs East wrote:
Tomasz Zielonka wrote:
I found it useful recently, when I needed zip functions for Trees - this way I didn't have to define functions for 3 trees, 4 trees, and so on.
Note also that:
repeat f `zwApply` xs = map f xs
When cooking up my own collection-y things (including splittable supplies, for example), I generally provide fmap and an equivalent of zwApply (a generic repeat is not quite so simple or useful). It's a nice little idiom, and a recommend it highly. ^^^^^
Funny you should choose that word: http://www.mail-archive.com/haskell@haskell.org/msg15073.html saves me banging the same old drum. Cheers Conor PS Many apologies for not having written this up yet! -- http://www.cs.nott.ac.uk/~ctm [I've moved again...]

On Thu, Dec 09, 2004 at 05:55:09PM +0000, Conor McBride wrote:
Funny you should choose that word:
http://www.mail-archive.com/haskell@haskell.org/msg15073.html
saves me banging the same old drum.
Is ap alias <# alias <%> for [] really the same as zwApply? Probably I am missing something. Best regards, Tomasz

Tomasz Zielonka wrote:
On Thu, Dec 09, 2004 at 05:55:09PM +0000, Conor McBride wrote:
Funny you should choose that word:
http://www.mail-archive.com/haskell@haskell.org/msg15073.html
saves me banging the same old drum.
Is ap alias <# alias <%> for [] really the same as zwApply? Probably I am missing something.
Yes and no. Depends which list monad you're using. zwApply is the <%> of one of the list idioms: it corresponds to the 'vectorizing' list monad whose return is repeat and whose join computes the diagonal of a matrix. But you're right: library ap for the 'list of successes' monad and zwApply do not coincide. I tend to use different list functors, depending on what they're for, so that all the plumbing is correctly cued from the types. Cheers Conor -- http://www.cs.nott.ac.uk/~ctm

Tomasz Zielonka writes:
On Thu, Dec 09, 2004 at 10:02:39AM -0500, Jan-Willem Maessen - Sun Labs East wrote:
And I thought that most programmers used "zipWith", which has to be prefix.
You can also use zipWith to simulate zipN, for any N (however, the following code uses infix notation):
Here's my favorite method, which I picked up from a paper whose title I
have forgotten:
Prelude> let zipWithN = (.repeat)
Prelude> let succ d f x = d (zipWith ($) f x)
Prelude> let zero = id
Prelude> let one = succ zero
Prelude> let two = succ one
Prelude> :t zipWithN two
zipWithN two :: forall b b1 b2.
(b -> b1 -> b2) -> [b] -> [b1] -> [b2]
Prelude> zipWithN two (,) [1..] (words "Haskell is great")
[(1,"Haskell"),(2,"is"),(3,"great")]
Prelude> let three = succ two
Prelude> :t zipWithN three
zipWithN three :: forall b b1 b2 b3.
(b -> b1 -> b2 -> b3) -> [b] -> [b1] -> [b2] -> [b3]
Prelude> :t zipWithN (succ three)
zipWithN (succ three) :: forall b b1 b2 b3 b4.
(b -> b1 -> b2 -> b3 -> b4) -> [b] -> [b1] ->
[b2] -> [b3] -> [b4]
Note that
zipWithN zero == repeat
and
zipWithN one == map
--
David Menendez
participants (17)
-
Ben Rudiak-Gould
-
Conor McBride
-
David Menendez
-
Douglas Bromley
-
Ferenc Wagner
-
Glynn Clements
-
Henning Thielemann
-
Jan-Willem Maessen - Sun Labs East
-
Josef Svenningsson
-
Jules Bean
-
Keith Wansbrough
-
Ketil Malde
-
Malcolm Wallace
-
Robert Dockins
-
Samuel Tardieu
-
Thomas Johnsson
-
Tomasz Zielonka