Re: [Haskell-cafe] Software Tools in Haskell

2008-01-06 Thread gwern0
On 2007.12.12 12:51:58 -0600, Tommy M McGuire [EMAIL PROTECTED] scribbled 
2.7K characters:
 Gwern Branwen wrote:
 Some of those really look like they could be simpler, like 'copy' -
 couldn't that simply be 'main = interact (id)'?
 Have you seen http://haskell.org/haskellwiki/Simple_Unix_tools?
 For example, 'charcount' could be a lot simpler - 'charcount = showln
 . length' would work, wouldn't it, for the core logic, and the whole
 thing might look like:
 main = do (print . showln . length) = getContents
 Similarly wordcount could be a lot shorter, like 'wc_l = showln .
 length . lines'
 (showln is a convenience function: showln a = show a ++ \n)

 Yes, that's absolutely true, and I am adding a section showing
 implementations based on interact as soon as I send this message.  The
 reason I didn't do so before is that I was trying to (to an extent)
 preserve the structure of the original implementations, which means using
 an imperative style.

Yes, I'm looking at it now. Pretty nice.

 Strangely, I have considerably more confidence in the imperative-ish
 Haskell code than I do in the imperative Pascal code, in spite of the fact
 that they are essentially the same.  Probably this is due to the
 referential transparency that monadic IO preserves and that does not even
 enter into the picture in traditional Pascal.  For example, the
 pseudo-nroff implementation has a giant, horrible block of a record
 (containing the state taken directly from KP) that is threaded through the
 program, but I am tolerably happy with it because I know that is the *only*
 state going through the program.

 Further, while interact could probably handle all of the filter-style
 programs (and if I understand correctly, could also work for the main loop
 of the interactive editor)

If your editor is referentially transparent, I think. Something like ed or sed 
could be done, as long as you didn't implement any of the IO stuff (like ! for 
ed).

 and a similar function could handle the later
 file-reading programs, I do not see how to generalize that to the
 out-of-core sort program.

Well, for out-of-core sort, someone several many months back posted a very neat 
solution using ByteStrings which iirc had performance as competitive as GNU 
sort's out-of-core sort

[much searching later]

Ah! Here we go: [Haskell-cafe] External Sort and unsafeInterleaveIO 
http://www.haskell.org/pipermail/haskell-cafe/2007-July/029156.html. I at 
least found it interesting.

 (Plus, interact is scary. :-D )

It's not scary! It's neat!

 I... I want to provide a one-liner for 'detab', but it looks
 impressively monstrous and I'm not sure I understand it.

 If you think that's bad :-)

 detab is one of the programs I do not like.  I kept the direct
 translation approach up through that, but I think it really hides the
 simplicity there; detab copies its input to its output replacing tabs with
 1-8 spaces, based on where the tab occurs in a line.  The only interesting
 state dealt with is the count of characters on each line, but that gets
 hidden, not emphasized.

 On the other hand, I'm not looking for one-liners; I really want clarity as
 opposed to cleverness.

Well, one-liners generally can be expanded to 2 or 3 lines if you want to add 
descriptive variable names. Better to start with a short version and expand it 
where unclear than have a long unclear one in the first place, right?

 One final comment: as regards run-length encoding, there's a really
 neat way to do it. I wrote a little article on how to do it a while
 ago, so I guess I'll just paste it in here. :)

 That *is* neat.

 --
 Tommy M. McGuire

Thanks. It took a while to write, but I never really found any place to put it 
up for other people to read.

--
gwern
GSM Submarine E. 510 ddnp building y friends RDI JCET


pgpHvlS1RIXiQ.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Software Tools in Haskell

2007-12-14 Thread Henning Thielemann

On Wed, 12 Dec 2007, Don Stewart wrote:

 ndmitchell:
 
  A much simpler version:
 
  main = print . length . words = getContents
 
  Beautiful, specification orientated, composed of abstract components.

 My thoughts too when reading the initial post was that it was all very
 low level imperative programming. Not of the Haskell flavour.

I remember there was a discussion about how to implement full 'wc' in an
elegant but maximally lazy form, that is counting bytes, words and lines
in one go. Did someone have a nice idea of how to compose the three
counters from implementations of each counter? I'm afraid one cannot
simply use the split and count fragments trick then.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Software Tools in Haskell

2007-12-14 Thread Benja Fallenstein
On Dec 14, 2007 9:29 AM, Henning Thielemann
[EMAIL PROTECTED] wrote:
 I remember there was a discussion about how to implement full 'wc' in an
 elegant but maximally lazy form, that is counting bytes, words and lines
 in one go. Did someone have a nice idea of how to compose the three
 counters from implementations of each counter? I'm afraid one cannot
 simply use the split and count fragments trick then.

Could you turn the folds into scans and use zip3 and last? I.e.,
something like this:

data Triple a b c = Triple !a !b !c deriving Show

countChars :: String - [Int]
countChars = scanl (\n _ - n+1) 0

countChar :: Char - String - [Int]
countChar c = scanl (\n c' - if c == c' then n+1 else n) 0

countLines = countChar '\n'
countWords = countChar ' '

last' [x] = x
last' (x:xs) = x `seq` last' xs

zip3' (x:xs) (y:ys) (z:zs) = Triple x y z : zip3' xs ys zs
zip3' _ _ _ = []

wc :: String - Triple Int Int Int
wc xs = last' $ zip3' (countChars xs) (countWords xs) (countLines xs)

main = print . wc = getContents

(or use Data.Strict.Tuple -- but that only has pairs and no zip...)

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


Re: [Haskell-cafe] Software Tools in Haskell

2007-12-12 Thread Neil Mitchell
Hi

 main = do (print . showln . length) = getContents
where showln a = show a ++ \n

This can be written better. print puts a newline at the end and does a
show, so lets remove that bit:

main = do (print . length) = getContents

Now we aren't using do notation, despite having a do block, and the
brackets are redundant:

main = print . length = getContents

Much nicer :-)

Thanks

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


Re: [Haskell-cafe] Software Tools in Haskell

2007-12-12 Thread Conal Elliott
Here's a version with cleaner separation between pure  IO:

main = interact $ show . length . words

  - Conal

On Dec 12, 2007 11:12 AM, Neil Mitchell [EMAIL PROTECTED] wrote:

 Hi

 Having got to the word counting example on the website:

 wordcount :: IO ()
 wordcount = do
wc - wordcount' False 0
putStrLn (show wc)
where
wordcount' inword wc = do
   ch - getc
   case ch of
   Nothing - return wc
   Just c - handlechar c wc inword
handlechar c wc _ | (c == ' ' ||
 c == '\n' ||
 c == '\t') = wordcount' False wc
handlechar _ wc False = wordcount' True $! wc + 1
handlechar _ wc True = wordcount' True wc

 Eeek. That's uglier than the C version, and has no abstract components.

 A much simpler version:

 main = print . length . words = getContents

 Beautiful, specification orientated, composed of abstract components.
 Code doesn't get much more elegant than that. Plus it also can be made
 to outperform C 
 (http://www-users.cs.york.ac.uk/~ndm/supero/http://www-users.cs.york.ac.uk/%7Endm/supero/
 )

 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] Software Tools in Haskell

2007-12-12 Thread Neil Mitchell
Hi

Having got to the word counting example on the website:

wordcount :: IO ()
wordcount = do
wc - wordcount' False 0
putStrLn (show wc)
where
wordcount' inword wc = do
   ch - getc
   case ch of
   Nothing - return wc
   Just c - handlechar c wc inword
handlechar c wc _ | (c == ' ' ||
 c == '\n' ||
 c == '\t') = wordcount' False wc
handlechar _ wc False = wordcount' True $! wc + 1
handlechar _ wc True = wordcount' True wc

Eeek. That's uglier than the C version, and has no abstract components.

A much simpler version:

main = print . length . words = getContents

Beautiful, specification orientated, composed of abstract components.
Code doesn't get much more elegant than that. Plus it also can be made
to outperform C (http://www-users.cs.york.ac.uk/~ndm/supero/)

Thanks

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


Re: [Haskell-cafe] Software Tools in Haskell

2007-12-12 Thread Tommy M McGuire

Don Stewart wrote:


My thoughts too when reading the initial post was that it was all very
low level imperative programming. Not of the Haskell flavour.

-- Don


Oh, heck yeah.  As I was thinking when I was translating it, I can't 
even say I'm writing Pascal code using Haskell; I wouldn't write Pascal 
code this way.


(IIRC, the xindex in translit that I mentioned uses several flag values 
in-band and I couldn't detangle the mess to figure them out, so I copied 
it as-is.  Ick.)



--
Tommy M. McGuire
[EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Software Tools in Haskell

2007-12-12 Thread Tillmann Rendel

Hi Tommy,

detab is one of the programs I do not like.  I kept the direct 
translation approach up through that, but I think it really hides the 
simplicity there; detab copies its input to its output replacing tabs 
with 1-8 spaces, based on where the tab occurs in a line.  The only 
interesting state dealt with is the count of characters on each line, 
but that gets hidden, not emphasized.


On the other hand, I'm not looking for one-liners; I really want clarity 
as opposed to cleverness.


I would do a simple, imperative feeling detab using a recursive [Char] 
processing function:


detab :: Int - String - String
detab width text = detab' width text where
  detab' tab [] = []
  detab' tab ('\n' : text) = '\n'  :  detab' width   text
  detab' tab ('\t' : text) = replicate tab ' ' ++ detab' width   text
  detab' 1   (char : text) = char  :  detab' width   text
  detab' tab (char : text) = char  :  detab' (tab-1) text

main = interact (detab 4)

In Haskell, using IO all over the place is the opposite of clarity, even 
in imperative feeling code wich basically encodes a main loop.


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


Re: [Haskell-cafe] Software Tools in Haskell

2007-12-12 Thread Benja Fallenstein
Another version of detab:

main = interact $ perLine $ concat . snd. mapAccumL f 0 where
f tab '\t' = (0, replicate (4-tab) ' ')
f tab char = ((tab+1) `mod` 4, [char])

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


Re: [Haskell-cafe] Software Tools in Haskell

2007-12-12 Thread Benja Fallenstein
On Dec 13, 2007 2:20 AM, Benja Fallenstein [EMAIL PROTECTED] wrote:
 Another version of detab:

 main = interact $ perLine $ concat . snd. mapAccumL f 0 where
 f tab '\t' = (0, replicate (4-tab) ' ')
 f tab char = ((tab+1) `mod` 4, [char])

Although on reflection, I think I might like the following compromise
with Tillmann's version best:

main = interact $ perLine $ detab 0 where
detab tab ('\t':cs) = replicate (4-tab) ' ' ++ detab 0 cs
detab tab (char:cs) = char  :  detab ((tab+1) `mod` 4) cs
detab tab = 

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


Re: [Haskell-cafe] Software Tools in Haskell

2007-12-12 Thread Benja Fallenstein
On Dec 13, 2007 2:28 AM, Benja Fallenstein [EMAIL PROTECTED] wrote:
 Although on reflection, I think I might like the following compromise
 with Tillmann's version best:

 main = interact $ perLine $ detab 0 where
 detab tab ('\t':cs) = replicate (4-tab) ' ' ++ detab 0 cs
 detab tab (char:cs) = char  :  detab ((tab+1) `mod` 4) cs
 detab tab = 

On more reflection, I wonder whether it would be worthwhile to have a
library function for folds that work from both left *and* right:

foldlr :: (a - b - c - (a,c)) - a - c - [b] - (a,c)
foldlr f l r [] = (l,r)
foldlr f l r (x:xs) = let (l',r') = f l x r''; (l'',r'') = foldlr f l' r xs
   in (l'',r')

main = interact $ perLine $ snd . foldlr detab 0  where
detab tab '\t' cs = (0, replicate (4-tab) ' ' ++ cs)
detab tab char cs = ((tab+1) `mod` 4, char : cs)

It's a fun function, anyway :-)

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


[Haskell-cafe] Software Tools in Haskell

2007-12-11 Thread Gwern Branwen
On 2007.12.10 13:52:41 -0600, Tommy McGuire [EMAIL PROTECTED]
scribbled 1.7K characters:

 In the if anyone is interested,... department

 For reasons that remain unclear, early this fall I started translating
 Brian W. Kernighan and P.J. Plaugher's classic _Software Tools in Pascal_
 into Haskell.  I have completed most of it, up to the second part of
 chapter 8 which presents a proto-m4 preprocessor.  I have the code online
 including notes, comments, descriptions, and a few alternate approaches.

 Attractions include:

 * A fair gamut of the usual Unix suspects: proto-cat, proto-wc, proto-tr,
 proto-compress, proto-ar, proto-grep, etc.

 * A usable editor, if you consider a de-featured ed-alike to be usable.

 * A simple monadic regular expression engine.

 * Zippers, Parsec, the State monad, the StateT monad transformer, and other
 attempts to sully Computing Science's brightest jewels.

 * Lots and lots of really bad Haskell, including a fair bit that is a
 direct translation of 30-year old Pascal (see xindex in translit, Ch. 2, if
 you need to skip lunch).  Programming really has advanced, you know.

 Anyway, the URL is:
   http://www.crsr.net/Programming_Languages/SoftwareTools

 Questions and comments would be appreciated, especially suggestions for how
 to make the code cleaner and more understandable.  Flames and mockery are
 welcome, too, but only if they're funny---remember, I've been staring at
 Haskell, Pascal (plus my job-related Perl, CORBA, and C++) for a while;
 there's no telling what my mental state is like.

 [I had intended to wait until I had the whole thing done to make this
 announcement, but I recently moved and have not made much forward progress
 since, other than putting what I had done online.]

 --
 Tommy M. McGuire

Some of those really look like they could be simpler, like 'copy' -
couldn't that simply be 'main = interact (id)'?

Have you seen http://haskell.org/haskellwiki/Simple_Unix_tools?

For example, 'charcount' could be a lot simpler - 'charcount = showln
. length' would work, wouldn't it, for the core logic, and the whole
thing might look like:

 main = do (print . showln . length) = getContents

Similarly wordcount could be a lot shorter, like 'wc_l = showln .
length . lines'

(showln is a convenience function: showln a = show a ++ \n)

I... I want to provide a one-liner for 'detab', but it looks
impressively monstrous and I'm not sure I understand it.

One final comment: as regards run-length encoding, there's a really
neat way to do it. I wrote a little article on how to do it a while
ago, so I guess I'll just paste it in here. :)

---

Recently I was playing with and working on a clone of the old Gradius
arcade games which was written in Haskell, Monadius
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Monadius-0.9.
Most of my changes were not particularly interesting (cleaning up,
Cabalizing, fixing warnings, switching all Integers to Ints and so
on), but in its Demo.hs, I found an interesting solution to an
interesting problem which seems to be a good example of how Haskell's
abstractions can really shine.

So, suppose we have these data items, which are levels which are
specified by a pair of numbers and then a long list of numbers, often
very repetitious. Perhaps a particular level might be represented this
way:

 level1 = ((Int,Int),[Int])
 level1 = 
 

[Haskell-cafe] Software Tools in Haskell

2007-12-10 Thread Tommy McGuire

In the if anyone is interested,... department

For reasons that remain unclear, early this fall I started translating 
Brian W. Kernighan and P.J. Plaugher's classic _Software Tools in 
Pascal_ into Haskell.  I have completed most of it, up to the second 
part of chapter 8 which presents a proto-m4 preprocessor.  I have the 
code online including notes, comments, descriptions, and a few alternate 
approaches.


Attractions include:

* A fair gamut of the usual Unix suspects: proto-cat, proto-wc, 
proto-tr, proto-compress, proto-ar, proto-grep, etc.


* A usable editor, if you consider a de-featured ed-alike to be usable.

* A simple monadic regular expression engine.

* Zippers, Parsec, the State monad, the StateT monad transformer, and 
other attempts to sully Computing Science's brightest jewels.


* Lots and lots of really bad Haskell, including a fair bit that is a 
direct translation of 30-year old Pascal (see xindex in translit, Ch. 2, 
if you need to skip lunch).  Programming really has advanced, you know.


Anyway, the URL is:
  http://www.crsr.net/Programming_Languages/SoftwareTools

Questions and comments would be appreciated, especially suggestions for 
how to make the code cleaner and more understandable.  Flames and 
mockery are welcome, too, but only if they're funny---remember, I've 
been staring at Haskell, Pascal (plus my job-related Perl, CORBA, and 
C++) for a while; there's no telling what my mental state is like.


[I had intended to wait until I had the whole thing done to make this 
announcement, but I recently moved and have not made much forward 
progress since, other than putting what I had done online.]




--
Tommy M. McGuire
[EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe