Re: how to write a simple cat

1999-06-01 Thread Friedrich Dominicus

Hannah Schroeter wrote:
> 
> Hello!
> 
> On Mon, May 31, 1999 at 06:01:31PM +0200, Friedrich Dominicus wrote:
> > Hannah Schroeter wrote:
> 
> > > Hello!
> 
> > > On Fri, May 28, 1999 at 08:00:27AM +0200, Friedrich Dominicus wrote:
> > > > I wrote before with my trouble understanding hugsIsEOF. But I don't have
> > > > found a clean way just to write a cat. Can s.o give me a hand?
> 
> > > import System(getArgs)
> > > file2stdout :: String {- filename -} -> IO ()
> 
> > could you explain that to me?
> 
> "{- filename -}" is just a comment designating that that parameter
> shall be the filename of the file to be copied to stdout.

Oh mei, just a comment it's time for me to reread my book it should be
found there.

> 
> > If I want to do it line-by-line is is some combination from
> > getLine, putStr ?
> 
> If you want to do it line wise, you probably have to do some
> exception handling in the IO monad. I.e. you try to read a line,
> handle the EOF exception by just terminating, any other exception
> by re-throwing it. If getLine succeeds you output it and continue,
> using tail recursion.
> 
> That's something like this:
> 
> import IO (isEOFError,openFile,IOMode(ReadMode),hGetLine)
> 
> file2stdout filename = catch mainloop handler
>   where
> mainloop = do
>   handle <- openFile filename ReadMode
>   mainloop' handle
> mainloop' hdl = do
>   line <- hGetLine hdl
>   putStrLn line
>   mainloop' hdl
> handler err = if isEOFError err then return () else ioError err -- rethrow
> 
> But why make it difficult if there's readFile?

I want to do the following, read a file line by line and finding out
which line is longer than x-chars. I want to print out which lines are
so long. I think that can just be done line-wise.

Thanks for you answer I hope I got it right with that information.

Regards
Friedrich





Re: how to write a simple cat

1999-06-01 Thread Hannah Schroeter

Hello!

On Tue, Jun 01, 1999 at 06:58:32AM +0200, Friedrich Dominicus wrote:
> [...]

> I want to do the following, read a file line by line and finding out
> which line is longer than x-chars. I want to print out which lines are
> so long. I think that can just be done line-wise.

> Thanks for you answer I hope I got it right with that information.

longerThan :: String {- filename -} -> Int {- length limit -} -> IO ()
longerThan fn lenlim = do
content <- readFile fn
let li = lines content
fl = filter (\l -> length l > lenlim) li
putStr (unlines fl)

So, still no need to fuzz with file handles :-)

> Regards
> Friedrich

Regards, Hannah.





Re: how to write a simple cat

1999-06-01 Thread Sven Panne

Hannah Schroeter wrote:
> [...] So, still no need to fuzz with file handles :-)

... and no need to fuzz with intermediate names, either. :-) If you
define an operator for reversed function composition

   (.|) = flip (.)

and read it like a pipe in *nix, you get a one-liner:

   longerThan fn lenlim = readFile fn >>= lines .| filter (length .| (>lenlim)) .| 
unlines .| putStr

Whether this is more or less readable than Hannah's version is largely
a matter of personal taste.

Cheers,
   Sven
-- 
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen  Oettingenstr. 67
mailto:[EMAIL PROTECTED]D-80538 Muenchen
http://www.pms.informatik.uni-muenchen.de/mitarbeiter/panne





Re: how to write a simple cat

1999-06-01 Thread Friedrich Dominicus

Hannah Schroeter wrote:
> 
> Hello!
> 
> On Tue, Jun 01, 1999 at 06:58:32AM +0200, Friedrich Dominicus wrote:
> > [...]
> 
> > I want to do the following, read a file line by line and finding out
> > which line is longer than x-chars. I want to print out which lines are
> > so long. I think that can just be done line-wise.
> 
> > Thanks for you answer I hope I got it right with that information.
> 
> longerThan :: String {- filename -} -> Int {- length limit -} -> IO ()
> longerThan fn lenlim = do
> content <- readFile fn
> let li = lines content
> fl = filter (\l -> length l > lenlim) li
> putStr (unlines fl)

I want to try if I got it right. You're using lazy evaluation here with
readFile, is that correct? So after I read in a chunk form that file
into one large String, lines splits that line on a '\n' position. The
lines li are filtered and l is one line a String-List which is added to
fl all the filterd lines are then put back into on large String. Uff. Is
that nearly correct?


Sometimes I've got the feeling that Haskell drives me nuts. I really
have a hard time to learn that, but somtimes I feel that this is the way
to go. But everytime I try to do I/O I've got the feeling as I had never
programmed before.


This solution is quite nice. I now have one extra question (maybe two
;-) How can I combine the output with a line-number can I put that into
the filter? Or do I have to found another solution?

Regards
Friedrich





Re: how to write a simple cat

1999-06-01 Thread S. Alexander Jacobson

It would be nice if the prelude defined more general functions like:

> splitStr c s = left:case right of [] -> []; otherwise -> splitStr c (tail right)
>  where (left,right)=span (/=c) s

> joinStr c l = case l of []-> []; otherwise -> foldl1 (\x y->x++c:y) l

The implementation of lines and unlines with these is trivial.
Sven's code becomes:

> longlines minlen filename = 
>   readFile filename >>=
>   splitStr '\n' .| filter (\x->length x>=minlen) .| joinStr '\n' .| putStr

-Alex-

___
S. Alexander Jacobson   Shop.Com
1-212-697-0184 voiceThe Easiest Way To Shop


On Tue, 1 Jun 1999, Sven Panne wrote:

> Hannah Schroeter wrote:
> > [...] So, still no need to fuzz with file handles :-)
> 
> ... and no need to fuzz with intermediate names, either. :-) If you
> define an operator for reversed function composition
> 
>(.|) = flip (.)
> 
> and read it like a pipe in *nix, you get a one-liner:
> 
>longerThan fn lenlim = readFile fn >>= lines .| filter (length .| (>lenlim)) .| 
>unlines .| putStr
> 
> Whether this is more or less readable than Hannah's version is largely
> a matter of personal taste.
> 
> Cheers,
>Sven
> -- 
> Sven PanneTel.: +49/89/2178-2235
> LMU, Institut fuer Informatik FAX : +49/89/2178-2211
> LFE Programmier- und Modellierungssprachen  Oettingenstr. 67
> mailto:[EMAIL PROTECTED]D-80538 Muenchen
> http://www.pms.informatik.uni-muenchen.de/mitarbeiter/panne
> 







Re: how to write a simple cat

1999-06-01 Thread Sven Panne

Friedrich Dominicus wrote:
>[...] How can I combine the output with a line-number can I put that
> into the filter? Or do I have to found another solution?

Don't fear! Mr. One-Liner comes to the rescue:;-)

   longerThan fn lenlim = readFile fn >>= lines .| filter (length .| (>lenlim)) .| zip 
[1..] .| map (\(n,l) -> shows n ") " ++ l) .| unlines .| putStr

[ This mail is optimised for 1280x1024 in landscape mode... ]

Cheers,
   Sven
-- 
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen  Oettingenstr. 67
mailto:[EMAIL PROTECTED]D-80538 Muenchen
http://www.pms.informatik.uni-muenchen.de/mitarbeiter/panne





Re: how to write a simple cat

1999-06-01 Thread Friedrich Dominicus

Sven Panne wrote:
> 
> Friedrich Dominicus wrote:
> >[...] How can I combine the output with a line-number can I put that
> > into the filter? Or do I have to found another solution?
> 
> Don't fear! Mr. One-Liner comes to the rescue:;-)
> 
>longerThan fn lenlim = readFile fn >>= lines .| filter (length .| (>lenlim)) .| 
>zip [1..] .| map (\(n,l) -> shows n ") " ++ l) .| unlines .| putStr

Do you want to drive me away from learning Haskell? Who the hell can try
to write such functions? Is readabilty not a concern in Haskell?
> 
> [ This mail is optimised for 1280x1024 in landscape mode... ]

yes and with one completly diffent mindscape ;-)

Regards
Friedrich





Re: how to write a simple cat

1999-06-01 Thread Kevin Atkinson

Keith Wansbrough wrote:
> 
> Sven Panne wrote:
> 
> > > Don't fear! Mr. One-Liner comes to the rescue:;-)
> > >
> > >longerThan fn lenlim = readFile fn >>= lines .| filter (length .| (>lenlim)) 
>.| zip [1..] .| map (\(n,l) -> shows n ") " ++ l) .| unlines .| putStr
> 
> Friedrich wrote:
> 
> > Do you want to drive me away from learning Haskell? Who the hell can try
> > to write such functions? Is readabilty not a concern in Haskell?
> 
> I would have to agree, Sven does seem to be working hard to drive a
> beginner away from Haskell.  But he is illustrating an important
> coding style.  If we lay his function out on a few more lines, and
> replace his (|.) = flip (.) operator with the standard functional
> composition (.), we get the following:

Truthfully I think the forward composition ie (flip (.) ) makes the code
more natural to read as it can be read do this, than this, than this,
etc...  As opposed to do this to the result of this to the result of
this, etc...  The former can be read as a sequence of actions to
perform.

I just wish a standard operator is chosen for a) flip (.) and b) flip
($) instead of having everyone make up their own.  I don't really care
what it is.  I truthfully like >.> for flip (.) and # for flip ($) but I
can easily change.
-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Re: how to write a simple cat

1999-06-01 Thread Lars Henrik Mathiesen

> Date: Tue, 01 Jun 1999 17:32:22 +0200
> From: Sven Panne <[EMAIL PROTECTED]>

> Don't fear! Mr. One-Liner comes to the rescue:;-)
> 
>longerThan fn lenlim = readFile fn >>= lines .| filter (length .| (>lenlim)) .| 
>zip [1..] .| map (\(n,l) -> shows n ") " ++ l) .| unlines .| putStr

Are you sure he didn't want the _original_ line numbers?

   longerThan fn lenlim = readFile fn >>= lines .| zip [1..] .| filter (snd .| length 
.| (>lenlim)) .| map (\(n,l) -> shows n ") " ++ l) .| unlines .| putStr

Lars Mathiesen (U of Copenhagen CS Dep) <[EMAIL PROTECTED]> (Humour NOT marked)





Official release of Hugs 98

1999-06-01 Thread Mark Jones

~c [EMAIL PROTECTED]
~r Readme
~e






Re: how to write a simple cat

1999-06-01 Thread Lennart Augustsson

Keith Wansbrough wrote:

> Sven Panne wrote:
>
> > > Don't fear! Mr. One-Liner comes to the rescue:;-)
> > >
> > >longerThan fn lenlim = readFile fn >>= lines .| filter (length .| (>lenlim)) 
>.| zip [1..] .| map (\(n,l) -> shows n ") " ++ l) .| unlines .| putStr
>
> Friedrich wrote:
>
> > Do you want to drive me away from learning Haskell? Who the hell can try
> > to write such functions? Is readabilty not a concern in Haskell?
>
> I would have to agree, Sven does seem to be working hard to drive a
> beginner away from Haskell.  But he is illustrating an important
> coding style.

Not only that, but it's also a style that many of us find readable.  I would not have
used reverse composition, but otherwise it looks much like I think it should.
Of course, this can be a little hard to read if you're not used to it, but all you need
is practise. :-)

--

-- Lennart








Re: how to write a simple cat

1999-06-01 Thread Jan Skibinski



On Tue, 1 Jun 1999, Sven Panne wrote:

> Friedrich Dominicus wrote:
> >[...] How can I combine the output with a line-number can I put that
> > into the filter? Or do I have to found another solution?
> 
> Don't fear! Mr. One-Liner comes to the rescue:;-)

How about initiating Haskell Newbie FAQ with such one-liners,
etc.? In a spirit of old Smalltalk-80 tutorials - organized
conceptually? To be quickly evaluated in Hugs?

I know, we all have something else to do than to take on extra
responsibilities. But if someone could donate an access to a
fast web server (mine is just too slow) then we could go
along Wiki-Wiki Web Server concepts  
(http://c2.com:8080/WikiWikiWeb) and have such FAQ pages 
generated by Haskell community at large. Say, you have
some good idea and some time - you connect to such server,
quickly edit your piece and go away. Since everybody could later
improve your piece, add another "pearl" or throw extra
comment in, this could lead to a well designed tutorial for
newbies.

I was recently quite impressed with what Squick (free
reincarnation of Smalltalk-80 plus..) people have done
with their Swiki. See, for example:
http://www.cc.gatech.edu/fac/mark.guzdial/squeak/pws/
Existing clones of Wiki-Wiki run in Perl, Python and Smalltalk.
Why not in Hugs, by the way?

Jan














Re: Implementation of Nameable Type Parameters

1999-06-01 Thread Kevin Atkinson

Kevin Atkinson wrote:
> 
> For those of you who may be interested:
> 
> I am working on an implementation of Nameable Type Parameters written in
> Haskell.  I currently have them working in a so called Mini Haskell
> where all kind information is presented explicitly.  I had a few
> unification problems but I eventually got it all working out.   It even
> allows overlapping instances!  I will let you know when I have a
> finished product which includes complete kind inference.  If anyone is
> interest in seeing the preliminary product please let me know and I will
> send you a copy.

This "Mini Haskell" only has unification and kind inference. It is just
enough to demonstrate how Nameable Type Parameters work.  Sorry if
anyone though it was a complete Haskell like system.

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Re: how to write a simple cat

1999-06-01 Thread Keith Wansbrough

Sven Panne wrote:

> > Don't fear! Mr. One-Liner comes to the rescue:;-)
> > 
> >longerThan fn lenlim = readFile fn >>= lines .| filter (length .| (>lenlim)) .| 
>zip [1..] .| map (\(n,l) -> shows n ") " ++ l) .| unlines .| putStr

Friedrich wrote:

> Do you want to drive me away from learning Haskell? Who the hell can try
> to write such functions? Is readabilty not a concern in Haskell?

I would have to agree, Sven does seem to be working hard to drive a
beginner away from Haskell.  But he is illustrating an important
coding style.  If we lay his function out on a few more lines, and
replace his (|.) = flip (.) operator with the standard functional
composition (.), we get the following:

  longerThan fn lenlim
= readFile fn >>= procFile

  procFile
= putStr .
  unlines.
  (map (\ (n,l) -> show n ++ ") " ++ l)) .
  (zip [1..]).
  (filter ( (>lenlim) . length ) )   .
  lines

  -- warning: untested code, sorry in advance for any typos...

This program is a good example of the use of higher-order functions.
First, note that (.) is function composition: so  f . g  is a function
that takes an argument (say x) and returns  f (g x)  : it applies g
first, and then applies f to the result.  So read the definition of
procFile backwards.

procFile is given the contents of the file as a String argument by

  readFile fn >>= procFile

Now it splits it into lines, yielding a list of lines, type [String].

Next we use a standard function, filter, which goes over a list
throwing out elements that don't match a given test.  Here the test is
(>lenlim) . length  - in other words, find the length of the string,
and then check if it is greater than lenlim.  If it isn't, throw it
out.  We now have a new list of type [String] containing all lines
longer than lenlim.

Now we use another standard function, zip.  This takes two lists (like
the two sides of a zipper) and merges them into one list, containing
pairs of elements: zip [1,2,3] ["Alpha","Bravo","Charlie"] gives
[(1,"Alpha"),(2,"Bravo"),(3,"Charlie")].  Here we pass the list
[1,2,3,4,5,6,...] (which goes on forever) as the first argument; zip
stops when the second list runs out.  So at the end of this stage we
have a list of pairs of line number and contents of line: type is
[(Integer,String)].

Next we use *another* standard function, map.  This applies a given
function to every element of the list.  Here the function is (\ (n,l)
-> show n ++ ") " ++ l).  This takes a pair (n,l), n being the line
number and l the line, and returns the concatenation of the number as
a string (show n), a close paren (to make it look nice), and the
original line (l).  We now have a list of strings again: ["1) Alpha",
"2) Bravo", "3) Charlie"].

Finally, we use unlines to turn the list into a single string
separated by newlines, and we print it out with putStr.

The neat trick here is that by using (.) we don't have to give names
to the intermediate results of the computation.  This works because in
Haskell you don't have to give all the parameters for a function; you
can miss out the last one and instead of getting an answer, you get
another function that takes the last parameter and gives you the
answer.  This is called currying, after the last name of the guy
Haskell is named after (Haskell B. Curry).

Hope this hasn't confused you too much.  One of Haskell's features is
that it is a very concise language; this is both good and bad.  You
get used to it after a while.

--KW 8-)

 






Announcing Hugs 98

1999-06-01 Thread Mark P Jones

__   __ __  __     ___ _
||   || ||  || ||  || ||__ Hugs 98: Based on the Haskell 98 Standard
||___|| ||__|| ||__||  __||Copyright (c) 1994-1999
||---|| ___||  World Wide Web: http://haskell.org/hugs
||   ||Report bugs to: [EMAIL PROTECTED]
||   || Version: May 1999  _


   We are pleased to announce a new release of Hugs, a Haskell
   interpreter and programming environment for developing cool
   Haskell programs.  Sources and binaries are freely available
   by anonymous FTP and on the World-Wide Web.  The release and
   supporting documents can be downloaded from the Hugs home page
   at: http://haskell.org/hugs

   This release is largely conformant with Haskell 98, including
   monad and record syntax, newtypes, strictness annotations, and
   modules.  In addition, it comes packaged with the libraries defined
   in the most recent version of the Haskell Library Report and with
   extension libraries that are compatible with GHC 3.0 and later.

   Additional features of the system include:

   o "Import chasing": a single module may be loaded, and Hugs will
 chase down all imports as long as module names are the same as
 file names and the files are found in the current path.

   o A simple GUI for Windows to facilitate program development.

   o Library extensions to support concepts such as concurrency,
 mutable variables and arrays, monadic parsing, tracing (for
 debugging), graphics, and lazy state threads.

   o A Win32 library for complete access to windows, graphics, and
 other important OS functionalities and a graphics library for
 easy access to Win32 graphics.

   o A "foreign interface" mechanism to facilitate interoperability
 with C.

   Hugs is best used as a Haskell program development system: it boasts
   extremely fast compilation, supports incremental compilation, and
   has the convenience of an interactive interpreter (within which one
   can move from module to module to test different portions of a
   program).  However, being an interpreter, it does not nearly match
   the run-time performance of, for example, GHC or HBC.

   Send email to [EMAIL PROTECTED] to join the hugs-users
   mailing list.  Bug reports should be sent to [EMAIL PROTECTED]
   Send email to [EMAIL PROTECTED] to subscribe to the
   hugs-bugs list.

   The home page for Hugs is at http://www.haskell.org/hugs.

--
 Hugs 98 is Copyright (c) Mark P Jones, Alastair Reid and the Yale Haskell
 Group 1994-99, and is distributed as Open Source software under the
 Artistic License; see the file "Artistic" that is included in the
 distribution for details.
--