Re: Haskell conventions (was: RE: how to write a simple cat)

1999-06-15 Thread Jan de Wit

On Fri, 11 Jun 1999, Erik Meijer wrote:

Personally I find the convention of using `a', `b', and `c' for type
variables to be a poor one.  I much prefer using `t' (if there's
only one) or `t1', `t2', ... (if there's more than one).
I find that for me this makes it much easier to read type declarations,
because names like `a', `b', and `c' sound like values, whereas names
like `t1', `t2', and `t3' suggest types.
   
   I *love* to use the same name for type variables and term variables, as in 
   
   f :: a - a
   f = \a - a
   
   I also love to use the same name for type constructors and value constructors, as 
in
   
   data Foo a = Foo a
   
   Erik
   

I also am quite fond of using selectors, like this:

data Foo a = Foo { unFoo :: a }

So that you have
  foo :: a - Foo a
unFoo :: Foo a - a

In my experience this works best with newtype declarations which are
in some sense isomorphic to the arguments, ie 

newtype Compose ff gg a = Compose { unCompose :: ff (gg a) } and suchlike.

Jan de Wit







RE: Haskell conventions (was: RE: how to write a simple cat)

1999-06-11 Thread Frank A. Christoph

Jonathan King wrote:
transformListElems :: (elem - elem') - List elem - List elem'
transformListElems transform Nil = Nil
transformListElems transform (Cons elem elemRest) =
  Cons (transform elem) (transformListElems transform elemRest)

 Well, the second version does more than just use descriptive variable
 names (and some not very descriptive, for that matter).  It also spells
 out constructors, has an especially long-winded function name, and uses
 one name for both a type variable and an argument (and a "primed" version
 for a second type variable).

Heh. :) I agree that using different constructor names is probably going
overboard, but when I look at industrial-strength C++ code it is not at all
uncommon to see such long-winded, redundant definitions, although they
usually aren't so polymorphic.

 You point out that short variable names keep code segments short, but my
 take on the why Haskell seems to "prefer" short names in many situations
 is that they are easier to think of as being *generic*.  (Intuitively,
 when you make a concept something more specific, it tends to get a longer
 name.)

That thought occurred to me too, but I had to reject it. Variable names can
be chosen in at least two ways: according to their domain (e.g., "File," or
less concretely, "f"), or according to the role they play in the definition
in question (e.g., "elem" or "kont"). If the variable is completely
polymorphic (or generalized), then its domain is essentially unrestricted,
but it still has a particular role to play.

Maybe a better motivation/explanation is simply that the descriptiveness of
a variable name is typically inversely proportional to the size of its
scope, where, realistically, the measure of scope size should involve both
textual length and expression size.

  Of course, for more involved definitions, it is better to use
  descriptive names.

 Well, for more specific definitions, anyway.  If I've got the style right.

For more specific definitions too. But if, say, you reimplemented a function
with a more efficient algorithm, you might be persuaded to use more
descriptive names, at least internally. But maybe you're right and
"specific" is more specific than "involved." :)

--FC






Re: Haskell conventions (was: RE: how to write a simple cat)

1999-06-11 Thread Keith Wansbrough

Jonathan King writes:

 So, the name of a type is always at least a full word, as are the names of
 specific functions.  But type variables are almost always single
 characters, and distinct from the names of any type.  Conventionally, they
 are also usually "a", "b", and "c", although "m" is for monad.
 Conventionally also, generic function arguments are "f" and "g", the
 conventional predicate is "p". Generic arguments are "x" and "y" (or "xs"
 and "ys" if they are lists); arguments with specified types are usually
 the first letter of their type name (e.g., "c" for Char, "i" for an Int;
 "n" and "m" are indices)... that covers most of it, I think.
 
 I think most of the Haskell code I've ever seen that *wasn't* written by
 me follow these conventions pretty closely.  But the strange thing is...I
 haven't found a prominent place on, e.g., the Haskell home page where this
 is spelled out. (Please tell me if I'm missing anything obvious.) In a
 way, I guess this is trivial, but I know from hard experience it can often
 take a long time to become completely aware of trivial things.

I think this kind of thing is valuable... Hungarian notation [1] serves the same 
purpose in Windows C / C++ programming.  It *is* valuable having canonical variable 
names for most situations; it reduces the intellectual load on the (human) reader of 
the code... you don't have to check back to the type signature and argument list to 
figure out what a particular variable denotes; it's just obvious from the name.

--KW 8-)


[1] @Article{
   Simonyi*91:Hungarian,
   author="Charles Simonyi and Martin Heller",
   title="The {H}ungarian Revolution",
   journal="{BYTE}",
   year="1991",
   volume="16",
   number="8",
   pages="{131--138}",
   month=aug,
   abstract="For all the attention given to names in the literature and
  magic (for to name a thing is to control it), names in programming
  languages have received curiously little attention.  Although
  today's computer programming languages force a rigid syntax on
  the programmer, they permit the use of more or less arbitrary
  names for variables, functions, and macros.  A reasonable standard
  for variable naming helps the development and maintenance of
  software.",
}


-- 
: Keith Wansbrough, MSc, BSc(Hons) (Auckland) :
: PhD Student, Computer Laboratory, University of Cambridge, England. :
:  (and recently of the University of Glasgow, Scotland. [] )   :
: Native of Antipodean Auckland, New Zealand: 174d47' E, 36d55' S.:
: http://www.cl.cam.ac.uk/users/kw217/  mailto:[EMAIL PROTECTED] :
:-:







Re: how to write a simple cat

1999-06-11 Thread Friedrich Dominicus

 I disagree, small scripts spend most of the time doing I/O if I don't
 understand how to do that I'm not able to even write the most simple
 things. This is eg. true for my cat ...
 
 I disagree. You need to know more about Functional Programming
 (and also the Haskell type system and its IO system) before
 you should try to solve your problems. It's like you want
 to drive without knowing anything about the engine, brakes, ...

What a comparison. I've nearly learned the languages I know of while
trying to solve  problems which come it's way. And this was just one
problem I were not able to figure out. It is trivial and don't expect
too much, so it was a good think trying out.

 
 There are many great introductory books which would
 give you an idea about some of the basic building blocks
 of "functional" software development.

I have tow of them: "Structure and interpretation of Computer Programs"
and "The Craft of FP programming using Haskell" The example I choose can
be found in Chapter 17 and it did not work this way, and what was is a
simple cat. So I asked why that example didn't work. I got very good and
interesting answers and have said thanks.



 
 I think both versions are really simple to write.

The may be of somone who knows FH, they are damn hard for someone
lacking that knowledge. If you are planning to write an Eiffel program
you and you have such a trouble with that problem in Eiffel you are very
welcome to send a note to the Eiffel- mailing lists. I don't think that
you will get an answer, first learn OOP than  ask

Regards
Friedrich





Re: Haskell conventions (was: RE: how to write a simple cat)

1999-06-11 Thread Craig Dickson

Jan Skibinski [EMAIL PROTECTED] wrote:

 But there are some stylistic camps, such as Eiffel's, that
 prefer names with underscores rather than Hungarian notation
 - claiming exactly the same reason: better readability. :-)

I don't see that underscores serve readability in the same way as Hungarian
notation purports to (unless the Eiffel people claim that underscores
somehow convey type information?), so I don't see a conflict here. One could
easily use both, e.g. n_widget_count for an integer value.

Whether underscores are better than mixed case, or whether Hungarian
notation is useful, seem to be matters of personal taste, not of fact. I
personally don't see much advantage to either underscores or mixed case
(except in C++, where many programmers tend towards such lengthy names that
the use of mixed case instead of underscores is actually helpful in keeping
identifier lengths under control). I use Hungarian notation only in C/C++,
and only when writing specifically for MS Windows, simply because that's the
convention on that platform (all of MS's documentation and samples use it).
I tend to think (getting off topic here) that Hungarian notation is fairly
useless; I'd rather know something about the scope of a variable (e.g. is it
a global? file-static? class member? static class member? local? static
local? In C++ there are so many possibilities! And that's not even
considering "const", "mutable", "volatile"...) so that I can see what the
variable relates to and how widely-felt the effects of changing it might be.
One company I worked at a few years back had a cute prefix scheme for this:
non-static member variables were prefixed "my" (i.e. owned by a single
object), static members "our" (i.e. shared by a class of objects), globals
and file-statics "the" (i.e. there can only be one), and locals "a" or "an"
(depending, of course, on whether the variable name began with a consonant
or a vowel). In practice, this seemed to my then-co-workers and me to be far
more helpful than Hungarian notation.

Craig







Re: Haskell conventions (was: RE: how to write a simple cat)

1999-06-11 Thread Christian Sievers

 So, the name of a type is always at least a full word, as are the names of
 specific functions.  But type variables are almost always single
 characters, and distinct from the names of any type.  Conventionally, they
 are also usually "a", "b", and "c", although "m" is for monad.
 Conventionally also, generic function arguments are "f" and "g", the
 conventional predicate is "p". Generic arguments are "x" and "y" (or "xs"
 and "ys" if they are lists); arguments with specified types are usually
 the first letter of their type name (e.g., "c" for Char, "i" for an Int;
 "n" and "m" are indices)... that covers most of it, I think.

I've never thought about a difference between i (and j) on the one
hand and n and m on the other, besides I would use i, j more locally,
if there were such a difference. So I might use i-[1..n], but would
nearly never use  n-[1..i].
If I don't do pattern matching on a list, I sometimes use l.
Otherwise, I use (a:as) as well as (x:xs) for lists.
I'm in trouble when it comes to @-patterns: is xs@(x:_) acceptable?
For non-integral numbers, I often use x, y.

 I think most of the Haskell code I've ever seen that *wasn't* written by
 me follow these conventions pretty closely.  But the strange thing is...I
 haven't found a prominent place on, e.g., the Haskell home page where this
 is spelled out. (Please tell me if I'm missing anything obvious.) In a
 way, I guess this is trivial, but I know from hard experience it can often
 take a long time to become completely aware of trivial things.

I've seen the (x:xs) (or whatever letter you want, BTW I'd use (f:fs)
for a list of functions) convention written somewhere. Most of the
rest is what is usually used in mathematics or is done in any computer 
language (such as c for Char).
Yes, a list of these things might be helpful.


Christian Sievers





Re: Haskell conventions (was: RE: how to write a simple cat)

1999-06-11 Thread Jan Skibinski



On Fri, 11 Jun 1999, Craig Dickson wrote:

 I don't see that underscores serve readability in the same way as Hungarian
 notation purports to (unless the Eiffel people claim that underscores
 somehow convey type information?), so I don't see a conflict here. One could
 easily use both, e.g. n_widget_count for an integer value.

The only readability advantage of underscores is when
someone starts including abbreviations within the names.
PAToVA?
PAtoVA?
PA_to_VA? [Whatever PA and VA means]

Often such abbreviations are not justifyable, but
some might be well known and accepted
within a given project.

What is important is a consistency - as you pointed it out
when speaking about "my", "own", "a" (
Smalltalk uses it too for local variables)
"the", etc.

But what really counts and is well stressed in Eiffel
are two things:
- avoid duality caused by side effects; that is: "set"
  type procedures never-never return anything but void.
 
  In low-level C programming practises people
  often oversuse the mixed "get-set" approach.
  Sometimes one does not have a choice (efficiency reasons)
  but often it is just a matter of bad habits. 
  Fortunatelly, Haskell does not have this sort of problems.
  
- document your routines according to return types:
void - verbs to indicate actions [perhaps monads in
   Haskell?]
bool - "True if .." or "Is ... ?"
other objects - nouns (possibly with adjectives) 

Looking back on what Prelude does - I do not think
there is any consistent naming rule with respect
to a noun-verb question. 

Jan







Re: Haskell conventions (was: RE: how to write a simple cat)

1999-06-11 Thread Jan Skibinski



 I think this kind of thing is valuable... Hungarian notation [1] 
 serves the same purpose in Windows C / C++ programming.  It *is* 
 valuable having canonical variable names for most situations; it reduces
the
 intellectual load on the (human) reader of the code... you don't have to
 check back to the type signature and argument list to figure out what a
 particular variable denotes; it's just obvious from the name.

But there are some stylistic camps, such as Eiffel's, that
prefer names with underscores rather than Hungarian notation
- claiming exactly the same reason: better readability. :-)

Jan







Re: how to write a simple cat

1999-06-10 Thread Rainer Joswig

At 16:37 Uhr +0200 09.06.1999, Friedrich Dominicus wrote:

  I think exercise with the purely functional, non-I/O core (and perhaps
  interact like someone else suggested) teaches you the mode of
  thinking in purely functional languages. That thinking can also
  help you understand the way I/O is implemented in a referentially
  transparent way.

I disagree, small scripts spend most of the time doing I/O if I don't
understand how to do that I'm not able to even write the most simple
things. This is eg. true for my cat ...

I disagree. You need to know more about Functional Programming
(and also the Haskell type system and its IO system) before
you should try to solve your problems. It's like you want
to drive without knowing anything about the engine, brakes, ...

There are many great introductory books which would
give you an idea about some of the basic building blocks
of "functional" software development. I don't think
"Haskell" is the problem - it's the way of thinking - you
need to "unlearn" previous knowledge about coding
algorithms. For your pleasure ;-) , lazy FP code in Lisp:

(defun longerThan (filename lenlim)
  (series:iterate ((l (series:choose-if
   (lambda (l) ( (length l) lenlim))
   (series:scan-file filename #'read-line
(print l)))

Which is really similar in spirit to Hannah Schroeter's:

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 think both versions are really simple to write.


Rainer Joswig, "Lavielle" EDV Systemberatung GmbH  Co. KG, Lotharstrasse 2b,
D22041 Hamburg, Tel: +49 40 658088, Fax: +49 40 65808-202,
Email: [EMAIL PROTECTED] , WWW: http://www.lavielle.de/





Re: how to write a simple cat

1999-06-10 Thread Fergus Henderson

On 09-Jun-1999, Friedrich Dominicus [EMAIL PROTECTED] wrote:
 What's a HOF?

HOF is an acronym for Higher-Order Function.

-- 
Fergus Henderson [EMAIL PROTECTED]  |  "I have always known that the pursuit
WWW: http://www.cs.mu.oz.au/~fjh  |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.





RE: how to write a simple cat

1999-06-10 Thread Frank A. Christoph

What is difficult is that by using some predefined function, one can
express very much in very small code. I believe Haskell is even more
expressive than most OO languages with comparable libraries
(perhaps except Smalltalk, as that has also a very compact syntax).
 
   I havn't made my mind if that is positive of negative. Sometimes it
   remind me of Perl and I'm not a big lover from it.
 
  Somehow that's not really fair towards Haskell. Perl is made up
  of many special cases, and in some other places, you have to use
  major hackery to achieve some goal (mind the "OO" part of Perl,
  for just one example).

 Now Haskell is on the other hand not quite fair to me. It makes me look
 as if I never have seen or programmed. I'm not thinking I'm the king of
 hacking, but I'm quite able to write some pieces of code. If using
 Haskell I have the feeling to ran against a wall, if I have s.th whih is
 trivial in e.g Python I have to fight to find a solution in Haskell.
 Maybe that's unfairf but it's quite different from all the things I
 know.

I wouldn't call it "unfair". After all, no one forced you to learn Python,
and no one is forcing you to learn Haskell. (OK, maybe your professor or
someone is... :) But that is really beside the point. There are good reasons
(necessities, really) why Haskell does things like I/O differently from,
say, Python, and the contract you have entered into with the Haskell
designers is that, in the end, it will pay off if you use them. If you feel
that that contract has not been fulfilled, or will never been fulfilled,
then you should stop using Haskell.

My feeling, though, is that even if you never use Haskell "in anger," your
Weltanschauung as a programmer will be enriched by having experience with
Haskell's way of doing things. I think this is in particular the case with
Haskell's monads, because after you have mastered them to some degree you
know what an imperative language "is really doing" under the semantic hood.

  I think exercise with the purely functional, non-I/O core (and perhaps
  interact like someone else suggested) teaches you the mode of
  thinking in purely functional languages. That thinking can also
  help you understand the way I/O is implemented in a referentially
  transparent way.

 I disagree, small scripts spend most of the time doing I/O if I don't
 understand how to do that I'm not able to even write the most simple
 things. This is eg. true for my cat ...

While I/O is certainly important for real-world programming, that does not
necessarily mean it is the best place to start learning a programming
language. There are exercises other than cat that better illustrate the
significant characteristics of Haskell and functional programming in
general, at least if you are coming from the imperative programming camp.

   sorry this looks morre terrible to me than all solutions before, IMO
way
   to much parameters and the names don't give me a good hint of what e.g
   beforeMap does.
 
  That's a HOF
 What's a HOF?

Higher-order function. A function that takes a function as an argument. A
first-order function is one that doesn't take any functions; a second-order
function is one that takes a first-order function, and so on...

  that first splits something up to a list using splitFn
  (or with the generalization I mentioned, to a monad), then maps a
  function over that list (namely beforeMap, because it's mapped
  *before* the filter), filters something out (using the filterPredicate),
  then again maps a function (namely afterMap, because it's mapped
  *after* the filter), then somehow joins the list (or monad), using
  unSplitFn.

 I would like names which tell me what is done.

 I read in contents of a file
 I process it, I build a string ...

First, since many Haskell functions are (parametrically) polymorphic, they
are necessarily more abstract than what you may be used to, and it can be
difficult to give them an immediately recognizable name.

Second, functions like map, filter, fold, etc. may be unfamiliar to you, but
they are part of a well known paradigm variously called the Boom hierarchy,
the Bird  Wadler list combinators, and calculational programming (these
names are not really equivalent). This paradigm has a lot of internal
structure, and once you see the Big Picture, you will see how nicely and
prominently map and fold and so on fit into it, and why the choice of names
are relatively unimportant. (The reason is that these functions are actually
canonical in significant way, and consequently they are used very often.
BTW, these names are fairly widely accepted, except that map is sometimes
called map-car, and fold is sometimes called reduce.)

The same situation exists in mathematics. It may not mean much to you if
someone describes a string as a monoid, but it has a wealth of meaning to a
mathematician. Names like map and fold are idiomatic in the same way to a
functional programmer.

Third, it is actually quite common in 

Re: how to write a simple cat

1999-06-10 Thread Lars Lundgren

On Wed, 9 Jun 1999, Friedrich Dominicus wrote:
[snip]
 What's a HOF?
 
A Higher Order Function, the key to code reuse and abstraction.

  that first splits something up to a list using splitFn
  (or with the generalization I mentioned, to a monad), then maps a
  function over that list (namely beforeMap, because it's mapped
  *before* the filter), filters something out (using the filterPredicate),
  then again maps a function (namely afterMap, because it's mapped
  *after* the filter), then somehow joins the list (or monad), using
  unSplitFn.
 
 I would like names which tell me what is done.
 
 I read in contents of a file
 I process it, I build a string ...
 
 etc
 

Sounds fine, and the translation to haskell is very natural:

main :: IO()
main = do contents - readFile filename
  putStr (process contents)

process :: String - String
..

numberStrPair2String
  more accurately.
 
 why not build_number_string_pair?


because it does not build a number-string pair, it builds a string (from a
number-string pair).
 
 Sorry I havn't the Signature of Show in my mind bu of course it just
 builds a string.


If you know what it is doing it is easy to figure out the type.
Ok, so it takes something and converts it to a string - aha, the type must
be 

a - String
 
  I think exercise with the purely functional, non-I/O core (and perhaps
  interact like someone else suggested) teaches you the mode of
  thinking in purely functional languages. That thinking can also
  help you understand the way I/O is implemented in a referentially
  transparent way.
 
 I disagree, small scripts spend most of the time doing I/O if I don't
 understand how to do that I'm not able to even write the most simple
 things. This is eg. true for my cat ...

If you just want to read stdin and write to stdout - use interact, if you
whant to read a file - use readFile, if you want to write to a file - use
writeFile. What is the problem? I think you are making it harder than it
is.



/Lars L 









RE: how to write a simple cat

1999-06-10 Thread CC700110

Hello,
I am soon to be in my final year at university and am looking for some good
ideas for a final year project, relating to HUGS or Haskell.  Any ideas?

Thanks
Andrew

 --
 From: Rainer Joswig[SMTP:[EMAIL PROTECTED]]
 Sent: 10 June 1999 12:40
 To:   [EMAIL PROTECTED]
 Subject:  Re: how to write a simple cat
 
 At 16:37 Uhr +0200 09.06.1999, Friedrich Dominicus wrote:
 
   I think exercise with the purely functional, non-I/O core (and perhaps
   interact like someone else suggested) teaches you the mode of
   thinking in purely functional languages. That thinking can also
   help you understand the way I/O is implemented in a referentially
   transparent way.
 
 I disagree, small scripts spend most of the time doing I/O if I don't
 understand how to do that I'm not able to even write the most simple
 things. This is eg. true for my cat ...
 
 I disagree. You need to know more about Functional Programming
 (and also the Haskell type system and its IO system) before
 you should try to solve your problems. It's like you want
 to drive without knowing anything about the engine, brakes, ...
 
 There are many great introductory books which would
 give you an idea about some of the basic building blocks
 of "functional" software development. I don't think
 "Haskell" is the problem - it's the way of thinking - you
 need to "unlearn" previous knowledge about coding
 algorithms. For your pleasure ;-) , lazy FP code in Lisp:
 
 (defun longerThan (filename lenlim)
   (series:iterate ((l (series:choose-if
(lambda (l) ( (length l) lenlim))
(series:scan-file filename #'read-line
 (print l)))
 
 Which is really similar in spirit to Hannah Schroeter's:
 
 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 think both versions are really simple to write.
 
 
 Rainer Joswig, "Lavielle" EDV Systemberatung GmbH  Co. KG, Lotharstrasse
 2b,
 D22041 Hamburg, Tel: +49 40 658088, Fax: +49 40 65808-202,
 Email: [EMAIL PROTECTED] , WWW: http://www.lavielle.de/
 





Haskell conventions (was: RE: how to write a simple cat)

1999-06-10 Thread Jonathan King


Well, the cat has been skinned and boned, but I think I see a
shread of meat or two that hasn't been picked over yet...

On Thu, 10 Jun 1999, Frank A. Christoph wrote:

[some attributions missing...I hope you know who you are]

[big snip, about the fact that Haskell programs can be quite brief]

 Third, it is actually quite common in Haskell (in my experience at
 least) to use very non-descriptive names for local variables if the
 definition is short.  I think it helps readability because the program
 fragment is shorter as a result, and it is easier to see the
 relationship between all the elements. For example, compare:
 
   map :: (a - b) - [a] - [b]
   map f [] = []
   map f (x:xs) = (f x) : map f xs
 
   transformListElems :: (elem - elem') - List elem - List elem'
   transformListElems transform Nil = Nil
   transformListElems transform (Cons elem elemRest) =
 Cons (transform elem) (transformListElems transform elemRest)

Well, the second version does more than just use descriptive variable
names (and some not very descriptive, for that matter).  It also spells
out constructors, has an especially long-winded function name, and uses
one name for both a type variable and an argument (and a "primed" version
for a second type variable).  I would prefer to compare with:

   map :: (atype - btype) - [atype] - [btype]
   map transform [] = []
   map transform (head:rest) = (transform head) : map transform rest

Now, I wouldn't necessarily prefer that form to the "canonical" one, but I
think this is because the canonical one *is* canonical.  That is, there
are some additional Haskell conventions that really are not spelled out as
well as they might be.

You point out that short variable names keep code segments short, but my
take on the why Haskell seems to "prefer" short names in many situations
is that they are easier to think of as being *generic*.  (Intuitively,
when you make a concept something more specific, it tends to get a longer
name.)

So, the name of a type is always at least a full word, as are the names of
specific functions.  But type variables are almost always single
characters, and distinct from the names of any type.  Conventionally, they
are also usually "a", "b", and "c", although "m" is for monad.
Conventionally also, generic function arguments are "f" and "g", the
conventional predicate is "p". Generic arguments are "x" and "y" (or "xs"
and "ys" if they are lists); arguments with specified types are usually
the first letter of their type name (e.g., "c" for Char, "i" for an Int;
"n" and "m" are indices)... that covers most of it, I think.

I think most of the Haskell code I've ever seen that *wasn't* written by
me follow these conventions pretty closely.  But the strange thing is...I
haven't found a prominent place on, e.g., the Haskell home page where this
is spelled out. (Please tell me if I'm missing anything obvious.) In a
way, I guess this is trivial, but I know from hard experience it can often
take a long time to become completely aware of trivial things.

It's amusing, actually.  Haskell basically defines your indentation for
you, these conventions give you all your variable names, static
type-checking almost ensures program correctness...I guess students taking
their first Haskell course should all get As and all produce identical
code on their homework assignments. :-)

 Of course, for more involved definitions, it is better to use 
 descriptive names.

Well, for more specific definitions, anyway.  If I've got the style right.

jking







Re: how to write a simple cat

1999-06-09 Thread Hannah Schroeter

Hello!

On Fri, Jun 04, 1999 at 12:18:31PM +0200, Friedrich Dominicus wrote:

 [...]

  splitFilterMap unSplitFn afterMap filterPredicate beforeMap splitFn =
unSplitFn . map afterMap . filter filterPredicate . map beforeMap . splitFn
 [...]

 sorry this looks morre terrible to me than all solutions before, IMO way
 to much parameters and the names don't give me a good hint of what e.g
 beforeMap does. 

That's a HOF that first splits something up to a list using splitFn
(or with the generalization I mentioned, to a monad), then maps a
function over that list (namely beforeMap, because it's mapped
*before* the filter), filters something out (using the filterPredicate),
then again maps a function (namely afterMap, because it's mapped
*after* the filter), then somehow joins the list (or monad), using
unSplitFn.

  splitFilter unSplitFn filterPred splitFn =
splitFilterMap unSplitFn id filterPred id splitFn

That's just a specialization if there's no need for mapping a function
over the list before or after the filtering.

  lenGt limit list = length list  limit

That's used as filter predicate.

  processFile limit = splitFilter unlines (lenGt limit) lines
  -- for the unnumbered version
OR

 I think s.th in that directin is somewhar what I like more

  numberElems = zip [1..]

  number2str (nr,l) = show nr ++ '\t' : l
 I would not call it number2 s.th it does not expplain to me that
 something is printed so maybe 
 print_number_str_pair or the like would be fine for me

But the function doesn't print either. It converts to a string.
Therefore 2str. You could call it
  numberStrPair2String
more accurately.

  processFile limit = splitFilterMap unlines number2str (lenGt limit . snd)
id (numberElems . lines)

 I don't think that I could work with splitFilterMap. Nevertheless is
 shows me all way lead to ROME ;-)

Hmmm. I think using higher order functions to encapsulate programming
structures (i.e. function concatenations, applications, etc.) is one
thing that makes up functional programming.

Just consider standard combinators like
  map, filter, foldl, foldr, sequence (Monads ahead :-) ), ...

 I re-wrote that stuff in Python and I've to admit it's way easier to
 understand for me (not even talking of writing). But I think it was  a
 good example to learn how FP-trained would do it. It's a long long way
 to go;-)

Did you use the more functional parts of Python there? map? filter? :-)

 Regards
 Friedrich

Regards, Hannah.





Re: how to write a simple cat

1999-06-09 Thread Hannah Schroeter

Hello!

On Wed, Jun 02, 1999 at 01:29:12AM -0700, Simon Peyton-Jones wrote:

 [...]

  - Would people actually add stuff?  I'm a bit skeptical, but it would
be great to have my skepticism proved unfounded.  

I think, Friedrich and those who helped him could have posted their
questions and suggestions and answers to a Wiki-Wiki similarly easily
like to the Haskell mailing list.

Anyway, I think the interested questions of a learning person are
a good motor to provide answers, explanations, and so on that are
comprehensible for a "newbie" (as incomprehensible answers provoke
further questions, that often finally lead to something that's
understood by at least the one asking the questions, except s/he
gave up).

 Simon 

Hannah.





Re: how to write a simple cat

1999-06-09 Thread Friedrich Dominicus

Hannah Schroeter wrote:
 
 Hello!
 
 On Fri, Jun 04, 1999 at 12:29:45PM +0200, Friedrich Dominicus wrote:
  [...]
 
   What is difficult is that by using some predefined function, one can
   express very much in very small code. I believe Haskell is even more
   expressive than most OO languages with comparable libraries
   (perhaps except Smalltalk, as that has also a very compact syntax).
 
  I havn't made my mind if that is positive of negative. Sometimes it
  remind me of Perl and I'm not a big lover from it.
 
 Somehow that's not really fair towards Haskell. Perl is made up
 of many special cases, and in some other places, you have to use
 major hackery to achieve some goal (mind the "OO" part of Perl,
 for just one example).

Now Haskell is on the other hand not quite fair to me. It makes me look
as if I never have seen or programmed. I'm not thinking I'm the king of
hacking, but I'm quite able to write some pieces of code. If using
Haskell I have the feeling to ran against a wall, if I have s.th whih is
trivial in e.g Python I have to fight to find a solution in Haskell.
Maybe that's unfairf but it's quite different from all the things I
know. 

 
   Another difficulty is monadic I/O. Perhaps you should exercise
   programming with standard higher-order functions without I/O
   a bit more, so that you master that difficulty and don't have
   to *simultaneously* understand both the HOF things and I/O.
 
  That might be good advice but I/O is one of the most essential things
  and I have to know how to use it proper for writing small skripts.
 
 I think exercise with the purely functional, non-I/O core (and perhaps
 interact like someone else suggested) teaches you the mode of
 thinking in purely functional languages. That thinking can also
 help you understand the way I/O is implemented in a referentially
 transparent way.

I disagree, small scripts spend most of the time doing I/O if I don't
understand how to do that I'm not able to even write the most simple
things. This is eg. true for my cat ...

Till then
Friedrich





Re: how to write a simple cat

1999-06-09 Thread Hannah Schroeter

Hello!

On Fri, Jun 04, 1999 at 12:29:45PM +0200, Friedrich Dominicus wrote:
 [...]

  What is difficult is that by using some predefined function, one can
  express very much in very small code. I believe Haskell is even more
  expressive than most OO languages with comparable libraries
  (perhaps except Smalltalk, as that has also a very compact syntax).

 I havn't made my mind if that is positive of negative. Sometimes it
 remind me of Perl and I'm not a big lover from it.

Somehow that's not really fair towards Haskell. Perl is made up
of many special cases, and in some other places, you have to use
major hackery to achieve some goal (mind the "OO" part of Perl,
for just one example).

Haskell has a very small, rather regular core syntax, with a bit
of syntactical sugar on top (type classes [translated to
records of "methods"], list comprehensions, monadic do-expressions),
but that syntax allows to define rather high level functions
*in Haskell itself* (see the Hugs prelude for the definitions and
see that very few of those definitions are actually references to
primitives, for example), and usually with very clean definitions
(though the GHC prelude implementation sometimes uses hacks to
get more efficient implementations).

  Another difficulty is monadic I/O. Perhaps you should exercise
  programming with standard higher-order functions without I/O
  a bit more, so that you master that difficulty and don't have
  to *simultaneously* understand both the HOF things and I/O.

 That might be good advice but I/O is one of the most essential things
 and I have to know how to use it proper for writing small skripts.

I think exercise with the purely functional, non-I/O core (and perhaps
interact like someone else suggested) teaches you the mode of
thinking in purely functional languages. That thinking can also
help you understand the way I/O is implemented in a referentially
transparent way.

 [...]

 This comments helped me. So I think I will put them under my pillow;-)

 Regards and thanks
 Friedrich

Regards, Hannah.





Re: how to write a simple cat

1999-06-07 Thread Christoph Lueth



Hans Aberg [EMAIL PROTECTED] writes:

 Exactly how is this connection between the lambda calculus and
 category theory described? -- That is, one would expect to know that
 if one has a category of some sort, it is equivalent to the lambda
 calculus, or something like that.

There is a very beautiful connection here, which is explained at
length e.g. in [1]. In short, every simply typed lambda-calculus gives
rise to a a cartesian closed category (ccc) (by taking its term
model). On the other hand, every ccc gives us a simply typed
lambda-calculus, by considering its so-called internal language, which
has its objects as types, and its morphisms as terms: a morphism
f:A-- B is a a term of B in the context of a variable (or a tuple of
variables) of type A. These two mappings are adjoint (the internal
language construction is the right adjoint).

To get the untyped lambda-calculus, you move from ccc's to so-called
c-monoids, but I've forgotten the exact definition of that; it's like
a ccc, but without a terminal object I think to eliminate trivial
(one-point) models.

--Christoph.

[1]  
@Book{LambekScott,
  author =  "J.~Lambek and P.~J.~Scott",
  title =   "Introduction to Higher Order Categorical Logic",
  publisher =   "Cambridge University Press",
  year =1986,
  volume =  7,
  series =  "Cambridge studies in advanced mathematics"
}





Re: how to write a simple cat

1999-06-05 Thread Friedrich Dominicus

Lennart Augustsson wrote:
 
 Friedrich Dominicus wrote:
 
  That might be good advice but I/O is one of the most essential things
  and I have to know how to use it proper for writing small skripts.
 
 Actually, you can do a lot without learning about I/O.  The function `interact'
 
 converts a `String-String' function into an IO function which can be used
 at the top level.  Here are some simple examples:

Thank your very much, I'm sure this will help me a lot.

Regards
Friedrich





Re: how to write a simple cat

1999-06-04 Thread Hannah Schroeter

Hello!

On Wed, Jun 02, 1999 at 08:12:04AM +0200, Friedrich Dominicus wrote:
 [...]

 this seems to to the thing I would like it to do. I now have to check if
 the given fn is valid and raise an error if not so I do think I'll make
 it;-)

No you don't have to check fn. readFile checks and throws an exception
if the file doesn't exist or is not readable. As you don't have an
exception handler in your definition, the error is propagated outwards
to the calling code, which is probably a good thing to do.

 [...]

 So please allow me another question. Is that a way such functions are
 build? How it that reused? Does it make sense to write some extra
 functions for intermediate steps or should I try to learn that kind of
 programming.


 I have some problems with it because  a lot of work is just done in one
 Method. My knowledge comes from OO-programming and there it wouldn't be
 good style to do so much in one function.

Then split it up like you'd do in an OO language. I think, FP also
is good for writing small functions that do one thing well, and then
composing them in various ways (as you see, composing functions (and
perhaps also values) in Haskell is possible in very many various ways :-) ).

In the running example, I could imagine those auxiliary functions:

splitFilterMap unSplitFn afterMap filterPredicate beforeMap splitFn =
  unSplitFn . map afterMap . filter filterPredicate . map beforeMap . splitFn
-- perhaps make that more generic by using fmap and mfilter
-- with this definition (that seems to be something generic enough for
-- the Monad library...):
-- mfilter :: MonadPlus m = (a - Bool) - m a - m a
-- mfilter fn m = m = (\a - if fn a then mzero else return a)

splitFilter unSplitFn filterPred splitFn =
  splitFilterMap unSplitFn id filterPred id splitFn

lenGt limit list = length list  limit

processFile limit = splitFilter unlines (lenGt limit) lines
-- for the unnumbered version
  OR

numberElems = zip [1..]

number2str (nr,l) = show nr ++ '\t' : l

processFile limit = splitFilterMap unlines number2str (lenGt limit . snd)
  id (numberElems . lines)

 Regards
 Friedrich

Regards, Hannah.





Re: how to write a simple cat

1999-06-04 Thread Friedrich Dominicus

 
 Then split it up like you'd do in an OO language. I think, FP also
 is good for writing small functions that do one thing well, and then
 composing them in various ways (as you see, composing functions (and
 perhaps also values) in Haskell is possible in very many various ways :-) ).
 
 In the running example, I could imagine those auxiliary functions:
 
 splitFilterMap unSplitFn afterMap filterPredicate beforeMap splitFn =
   unSplitFn . map afterMap . filter filterPredicate . map beforeMap . splitFn
 -- perhaps make that more generic by using fmap and mfilter
 -- with this definition (that seems to be something generic enough for
 -- the Monad library...):
 -- mfilter :: MonadPlus m = (a - Bool) - m a - m a
 -- mfilter fn m = m = (\a - if fn a then mzero else return a)

sorry this looks morre terrible to me than all solutions before, IMO way
to much parameters and the names don't give me a good hint of what e.g
beforeMap does. 


 
 splitFilter unSplitFn filterPred splitFn =
   splitFilterMap unSplitFn id filterPred id splitFn
 
 lenGt limit list = length list  limit
 
 processFile limit = splitFilter unlines (lenGt limit) lines
 -- for the unnumbered version
   OR

I think s.th in that directin is somewhar what I like more
 
 numberElems = zip [1..]
 
 number2str (nr,l) = show nr ++ '\t' : l
I would not call it number2 s.th it does not expplain to me that
something is printed so maybe 
print_number_str_pair or the like would be fine for me
 
 processFile limit = splitFilterMap unlines number2str (lenGt limit . snd)
   id (numberElems . lines)

I don't think that I could work with splitFilterMap. Nevertheless is
shows me all way lead to ROME ;-)

I re-wrote that stuff in Python and I've to admit it's way easier to
understand for me (not even talking of writing). But I think it was  a
good example to learn how FP-trained would do it. It's a long long way
to go;-)


Regards
Friedrich





Re: how to write a simple cat

1999-06-04 Thread Mariano Suarez-Alvarez

On Thu, 3 Jun 1999, Hans Aberg wrote:

 A ``category with + and ^ '' is called cartesian closed aditive
 category, cf MacLane, Category Theory for the Working Mathematician
 
 Is this a suggestion or a theorem?

A definition.

-- m






Re: how to write a simple cat

1999-06-04 Thread Hans Aberg

At 14:18 +0200 1999/06/04, Mariano Suarez-Alvarez wrote:
 A ``category with + and ^ '' is called cartesian closed aditive
 category, cf MacLane, Category Theory for the Working Mathematician

 Is this a suggestion or a theorem?

A definition.

I did not see the connection between the + and ^ of MacLane with those of
lambda calculus: One thing that is needed is that if A, B are in the
category then also A^B = Hom(B, A) is in the category, and that might work
with a Cartesian closed category, which expresses the ^ operator as the
existence of an adjoint.

But why is the existence of
M + N = lambda a b. M(a)(N(a)(b))
the same thing as that the category is additive? For example, the Church
numeral functionals can be added, but they do not take values in an abelian
group.

Exactly how is this connection between the lambda calculus and category
theory described? -- That is, one would expect to know that if one has a
category of some sort, it is equivalent to the lambda calculus, or
something like that.

  Hans Aberg
  * Email: Hans Aberg mailto:[EMAIL PROTECTED]
  * Home Page: http://www.matematik.su.se/~haberg/
  * AMS member listing: http://www.ams.org/cml/







Re: how to write a simple cat

1999-06-04 Thread Lennart Augustsson

Friedrich Dominicus wrote:

 That might be good advice but I/O is one of the most essential things
 and I have to know how to use it proper for writing small skripts.

Actually, you can do a lot without learning about I/O.  The function `interact'

converts a `String-String' function into an IO function which can be used
at the top level.  Here are some simple examples:

-- Just copy stdin to stdout
main = interact id

-- Remove all Q from stdin
main = interact (filter (/= 'Q'))

-- Print the line number in front of each line
main = interact (unlines . zipWith (\n l - show n ++ " " ++ l)  [1..] . lines)

-- Print a sorted list of all words
import List
main = interact (unlines . nub . sort . concatMap words . lines)


Well, I'm sure you get the idea.

-- Lennart







Re: how to write a simple cat

1999-06-04 Thread Friedrich Dominicus

  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?
 
 Yes, filter applies the function parameter (in that case the lambda)
 to each element of the list parameter (2nd) to yield booleans, and
 returns a list of those elements of the original list, where the
 function yielded true.
 
  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.
 
 What is difficult is that by using some predefined function, one can
 express very much in very small code. I believe Haskell is even more
 expressive than most OO languages with comparable libraries
 (perhaps except Smalltalk, as that has also a very compact syntax).

I havn't made my mind if that is positive of negative. Sometimes it
remind me of Perl and I'm not a big lover from it.

 
 Another difficulty is monadic I/O. Perhaps you should exercise
 programming with standard higher-order functions without I/O
 a bit more, so that you master that difficulty and don't have
 to *simultaneously* understand both the HOF things and I/O.

That might be good advice but I/O is one of the most essential things
and I have to know how to use it proper for writing small skripts. And
Yes I'll train on higher-order-functions. But that's not all I've to
lean not to having to use all the  parameters a function has. A good
example for this is IMO foldx (l,r)




 
 Either look at the solutions with the "pipe" (.|) operator that
 have been posted. (I like them, btw :-) ). Or pre/postprocess the
 li/fl variables, depending on if you need the original line numbers
 or numbers for the generated lines.

I rewrote that sligthly to get it more in sync with the book I read they
are using . for it and I think I like it a bit better but reading it
as a pipe symbol is very helpful too.

 
 In the latter case, you can do this:
   let numbered_lines = zipWith (\lineno linecont -
   show lineno ++ "\t" ++ linecont)
[1..]
fl
   putStr (unlines numbered_lines)
 instead of the original putStr "statement".
 
 In the first case, you must attach line numbers to the original file
 contents. li is the list of lines.
   let li' = zip [1..] li
 creates a list of pairs (line number, line content).
 
 You must then adapt the filter function from \l - ... to
 \(_linenumber, l) - ..., to extract the line content from the
 (line number, content) pair.
 
 For the final output, you must convert the remaining (number,content)
 pairs from fl to single strings containing the line number in textual
 form, i.e.
   let fl' = map (\(number, content) - show number ++ "\t" ++ content) fl
   putStr (unlines fl')


This comments helped me. So I think I will put them under my pillow;-)

Regards and thanks
Friedrich





Re: how to write a simple cat

1999-06-03 Thread Hannah Schroeter

Hello, Friedrich.

On Tue, Jun 01, 1999 at 04:04:42PM +0200, Friedrich Dominicus wrote:
 [...]

  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?

In that example, lazy evaluation is not essential. But with strict
evaluation, that function needs memory proportional to the size
of the input file, while with lazy evaluation, it needs only memory
proportional to the length of the longest line in the file.
So to understand the basic working of that code, lazy vs strict
evaluation is irrelevant.

So, the statements are:

- read file fn into one large string named content
- split the lines of content into a list of strings named li
- choose from li those lines l where (\l - ...) l is true,
  i.e. whose length is  lenlim, bind fl to the result of that filtering
- fl is a list of strings (meaning lines), and unlines fl joins those
  lines into one string, which is output with putStr.

 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?

Yes, filter applies the function parameter (in that case the lambda)
to each element of the list parameter (2nd) to yield booleans, and
returns a list of those elements of the original list, where the
function yielded true.

 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.

What is difficult is that by using some predefined function, one can
express very much in very small code. I believe Haskell is even more
expressive than most OO languages with comparable libraries
(perhaps except Smalltalk, as that has also a very compact syntax).

Another difficulty is monadic I/O. Perhaps you should exercise
programming with standard higher-order functions without I/O
a bit more, so that you master that difficulty and don't have
to *simultaneously* understand both the HOF things and I/O.

 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?

Either look at the solutions with the "pipe" (.|) operator that
have been posted. (I like them, btw :-) ). Or pre/postprocess the
li/fl variables, depending on if you need the original line numbers
or numbers for the generated lines.

In the latter case, you can do this:
  let numbered_lines = zipWith (\lineno linecont -
  show lineno ++ "\t" ++ linecont)
   [1..]
   fl
  putStr (unlines numbered_lines)
instead of the original putStr "statement".

In the first case, you must attach line numbers to the original file
contents. li is the list of lines.
  let li' = zip [1..] li
creates a list of pairs (line number, line content).

You must then adapt the filter function from \l - ... to
\(_linenumber, l) - ..., to extract the line content from the
(line number, content) pair.

For the final output, you must convert the remaining (number,content)
pairs from fl to single strings containing the line number in textual
form, i.e.
  let fl' = map (\(number, content) - show number ++ "\t" ++ content) fl
  putStr (unlines fl')

 Regards
 Friedrich

Regards, Hannah.





Re: how to write a simple cat

1999-06-03 Thread Hans Aberg

At 20:08 +0200 1999/06/03, Mariano Suarez-Alvarez wrote:
A ``category with + and ^ '' is called cartesian closed aditive
category, cf MacLane, Category Theory for the Working Mathematician

Is this a suggestion or a theorem?

  Hans Aberg
  * Email: Hans Aberg mailto:[EMAIL PROTECTED]
  * Home Page: http://www.matematik.su.se/~haberg/
  * AMS member listing: http://www.ams.org/cml/







Re: how to write a simple cat

1999-06-03 Thread Mariano Suarez-Alvarez

On Wed, 2 Jun 1999, Hans Aberg wrote:

 But it can be a spin-off for thoughts: A category is essentially an object
 with I and *, and a functor is a map preserving those. So what about the
 two other operations, + and ^ ?.

A ``category with + and ^ '' is called cartesian closed aditive
category, cf MacLane, Category Theory for the Working Mathematician

Mariano Suarez Alvarez 







RE: how to write a simple cat

1999-06-02 Thread Frank A. Christoph

   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.

Good point. The compositional style emphasizes the fact that there is only
one object being transformed here. What can make this style more difficult
to read is all the permutations you need to inject for arguments of standard
operators.

 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.

The standard notation for flip (.) is ;, but unfortunately Haskell co-opted
this for lexical purposes...

--FC






RE: how to write a simple cat

1999-06-02 Thread Simon Peyton-Jones


   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.

haskell.org is the obvious place.  I'm sure John Peterson would be happy
to add stuff to the site.

Community-generated FAQ pages sound great, but

 - Some (standard? readily-available?) technology is needed to allow
   people to add stuff without intervention from the site organiser.
   The Wiki-Wiki-Web stuff indeed looks like a real possibility.  I didn't
   know about it; thanks for the pointer.  But someone has
   to set it up and host it.  Any volunteers?

 - Would people actually add stuff?  I'm a bit skeptical, but it would
   be great to have my skepticism proved unfounded.  

Simon 





RE: how to write a simple cat

1999-06-02 Thread Peter Hancock

 "Hans" == Hans Aberg [EMAIL PROTECTED] writes:

 One reason flip(.) might be given a symbol similar to multiplication and
 flip($) a symbol similar to exponentiation is that on the Church integer
 functionals, these two operations are just the multiplication and
 exponentiation of those integer functionals.

It would seem to follow that \lambda abstraction is a kind of
logarithm operator (with the bound variable as ``base''..)!

  Peter Hancock





RE: how to write a simple cat

1999-06-02 Thread Hans Aberg

At 12:44 +0100 1999/06/02, Peter Hancock wrote:
 One reason flip(.) might be given a symbol similar to multiplication and
 flip($) a symbol similar to exponentiation is that on the Church integer
 functionals, these two operations are just the multiplication and
 exponentiation of those integer functionals.

It would seem to follow that \lambda abstraction is a kind of
logarithm operator (with the bound variable as ``base''..)!

I don't know anything about that. The integers are (in quasi TeX notation)
 \bar n = lambda a b. a(...a(b)...)
where the a is repeated n times. It is fun to play with these in a
functional language. If inc is increment by 1, then then f(inc)(0) = n if f
= \bar n. For expressions M, N, Church defines
M + N = lambda a b. M(a)(N(a)(b))
M * N = lambda a. M(N(a))  -- Function composition.
M ^ N = N(M)
I would prefer to reverse the M and N in the right hand expressions of M
and N, though, which I think makes expressions become more logical.

Then together with the identity I, +, * and ^ can be written out to be a
primitive set for the lambda theory. That is, all lambda expressions can be
generated from these symbols.

  Hans Aberg
  * Email: Hans Aberg mailto:[EMAIL PROTECTED]
  * Home Page: http://www.matematik.su.se/~haberg/
  * AMS member listing: http://www.ams.org/cml/







RE: how to write a simple cat

1999-06-02 Thread Jan Skibinski


 haskell.org is the obvious place.  I'm sure John Peterson would be happy
 to add stuff to the site.
 
 Community-generated FAQ pages sound great, but
 
  - Some (standard? readily-available?) technology is needed to allow
people to add stuff without intervention from the site organiser.
The Wiki-Wiki-Web stuff indeed looks like a real possibility.  I didn't
know about it; thanks for the pointer.  But someone has
to set it up and host it.  Any volunteers?

The best thing to find it out is to examine the standard
procedures on the best Wiki-Wiki servers, such as Swiki
(Swiki Swiki page is devoted to the technology of Swiki
servers). In addition, we could get in touch with corresponding
system administrators and ask them about their headaches
with maintenance and security issues. I guess - they have some.
I could volunteer for this task providing that we have some
consensus here regarding usefulness of such server, available
network resources and our will to implement it.

As far as I know, the model is based on a complete anarchy
and a trust in good user intentions. Anyone can mess with
existing pages. Some users, not necessarily the system
administrator, would probably backup the stuff periodically
- just in case.

On another hand, the original Wiki-Wiki server has run
for several years. Swiki server has amazing number of
pages - ranging from documentation to collaborative
working platforms for variety of ideas for Squick. It
appears that it works somehow - otherwise their server
would have died several years ago when they started it all.  

 
  - Would people actually add stuff?  I'm a bit skeptical, but it would
be great to have my skepticism proved unfounded.  

One good example is provided by this thread. It would
be a shame if the results stayed burried here instead
of being exposed to a more public forum. I would
envision having the topic stated, followed by Keith excellent
explanation of his straightforward classical approach,
then by several demonstrations of how it could be done
by 'mean and lean' ways -- as provided by Sven and the
others. With explanation of motivations 'why'.
 
I would also love to see some links from there to
a general topic of operator compositions, to monads,
to IO, etc.

Some time ago, I witnessed here quite a hot and lengthy
discussion about exceptions in Haskell. Several models
were discussed, some of the stuff was to be implemented in GHC.
But I have not seen any final conclusions or a digest
made. If this was worthy of such a good discussion, then
it would be worthy to have it in FAQ as well.

I am also sure that those who teach would gladly expose
their own little tricks of trade, which are probably publicly
accessible anyway through their course pages.

Since we are not talking here about major scientific
breakthroughs, an individual ego would not horribly suffer
if someone corrected the author in public and found a better
style, solution or explanation. Links to the authors' pages
could also be provided. Swiki, for example, keeps local
references to contributors's resumes. They even go to
such extreme that other members add some kudos to such
pages as well.

Some netiquette policy could be established on how to delete
or modify the existing stuff - without offending original
contributors. But - judging from what I know about this
forum - this should never be a real problem. The idea is
to produce the best possible documents, which must therefore
be the subjects to pruning, modifications and reorganizations.

  
Jan








Re: how to write a simple cat

1999-06-02 Thread Sven Panne

Hans Aberg wrote:
 [...] Then together with the identity I, +, * and ^ can be written
 out to be a primitive set for the lambda theory. That is, all lambda
 expressions can be generated from these symbols.

Impressive!  %-)  Hmmm, I just thought about the possible directions
of this discussion if I had written the more general

   (.|) :: Functor f = f a - (a - b) - f b
   (.|) = flip fmap

instead...:-}

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-02 Thread Friedrich Dominicus

At first, thanks to all of you about this nice insight into FP used
programmers. It was really a suprise to me to see that that what Sven
wrote seems to be easily understood. I would really like to see such
code-snippets to found on a central site what about www.haskell.org ?

I reread my book and there the chapte about functional composition or
the like and I found  the stuff I didn't understand. So maybe it's time
to re-read the book again ;-)



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


This seems to be not workable and I tried it by myself. 

this is my Result:
lt1 fn lenlim = readFile fn = procFile lenlim

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


this seems to to the thing I would like it to do. I now have to check if
the given fn is valid and raise an error if not so I do think I'll make
it;-)

Another thing is that I prefer for 
(.|) = flip (.) 
(.) = flip(.)

I think that's a matter of tast an both are familar. The .| reminds me
of a pipe-symbol and  shows me the flow. So ok Both are quite ok
althought I'm quite aware taht f . g maybe well known in mathematics.
But it's quite amazing how many possibilities you have to express that.
This makes it very expressive but IMO terrible difficult to understand.
I hope I get used to use the "right" mental  model for FP someday. And I
hope I then won't the obfuscatd code but the beauty of Functions.

Thanks to Keith to explain to me in detail what is meant by the code
excepts. I rethink about it, read it again and now it's getting clearer
and clearer each time. Another 1000 examples and I may be familia with
it ;-)


So please allow me another question. Is that a way such functions are
build? How it that reused? Does it make sense to write some extra
functions for intermediate steps or should I try to learn that kind of
programming.


I have some problems with it because  a lot of work is just done in one
Method. My knowledge comes from OO-programming and there it wouldn't be
good style to do so much in one function.

Regards
Friedrich





RE: how to write a simple cat

1999-06-02 Thread trb

Simon Peyton-Jones writes:
  Community-generated FAQ pages sound great, but
  
   - Some (standard? readily-available?) technology is needed to allow
 people to add stuff without intervention from the site organiser.
 The Wiki-Wiki-Web stuff indeed looks like a real possibility.  I didn't
 know about it; thanks for the pointer.  But someone has
 to set it up and host it.  Any volunteers?

I don't think I have the bandwidth; I don't know where I would find time to
set it up; and I would be very worried about security of the server. Maybe it
would be best to use a dedicated server.

   - Would people actually add stuff?  I'm a bit skeptical, but it would
 be great to have my skepticism proved unfounded.  

Yes. Most of the Haskell I write is library code that I'm happy to LGPL.

Several people have mentioned the problem of standard names. A lot of the code I
write ends up as junk, when someone else writes it better or in a more standard
way. The rest tends to suffer from software rot, which partly results from
changing other code to make it more standard.

I've just been reading a paper (which I don't have at hand) on space profiling
with nhc. One code example uses a function called "tandem". I have a similar
function called "dropLen" (dropLen = flip tandem).

A convenient way to collaborate in building up a standard collection of useful
combinators would be very helpful.

Tim





RE: how to write a simple cat

1999-06-02 Thread Hans Aberg

At 11:57 +0900 1999/06/02, Frank A. Christoph wrote:
 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.

The standard notation for flip (.) is ;, but unfortunately Haskell co-opted
this for lexical purposes...

In math, f . g is written f o g, so for flip(.) I decided to use a filled
circle (filled o). This might be used the day Haskell goes Unicode. :-)

On flip($), one may note that in Church, "The Calculi of
Lambda-Conversion", the notation (written out here using TeX code) $M^N =
N(M)$ is used. So one may think of variations of an exponential as a symbol
for flip($).

One reason flip(.) might be given a symbol similar to multiplication and
flip($) a symbol similar to exponentiation is that on the Church integer
functionals, these two operations are just the multiplication and
exponentiation of those integer functionals.

  Hans Aberg
  * Email: Hans Aberg mailto:[EMAIL PROTECTED]
  * Home Page: http://www.matematik.su.se/~haberg/
  * AMS member listing: http://www.ams.org/cml/







Re: how to write a simple cat

1999-06-02 Thread Laszlo Nemeth


Hans Aberg wrote:

 But it can be a spin-off for thoughts: A category is essentially an object
 with I and *, and a functor is a map preserving those. So what about the
 two other operations, + and ^ ?.

I somehow managed to delete Hans's earlier post in which he gives the
definitions for + and ^. So I wanted to fetch them from the
archive...which was last updated on the 28 May. Is the archive broken
or just rarely updated?

Thanks,
 Laszlo Nemeth





Re: how to write a simple cat

1999-06-02 Thread Hans Aberg

At 16:46 +0200 1999/06/02, Sven Panne wrote:
 [...] Then together with the identity I, +, * and ^ can be written
 out to be a primitive set for the lambda theory. That is, all lambda
 expressions can be generated from these symbols.

Impressive!  %-)  Hmmm, I just thought about the possible directions
of this discussion if I had written the more general

   (.|) :: Functor f = f a - (a - b) - f b
   (.|) = flip fmap

instead...:-}

I should caution that I had to write out the operators I, +, *, and ^ in a
special way (which I do not immediately recall) in order to turn them into
a primitive set of the lambda calculus. Also, if one should admit constant
functions (which Church does not), one must add an operator O, which I
recall was
O = lambda a b. b
Then O(inc)(0) = 0, so it is probably the right one. Church's integer
functionals become extended to 0 by setting \bar 0 = O.

But it can be a spin-off for thoughts: A category is essentially an object
with I and *, and a functor is a map preserving those. So what about the
two other operations, + and ^ ?.

  Hans Aberg
  * Email: Hans Aberg mailto:[EMAIL PROTECTED]
  * Home Page: http://www.matematik.su.se/~haberg/
  * AMS member listing: http://www.ams.org/cml/







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





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

 






Re: how to write a simple cat

1999-05-31 Thread Friedrich Dominicus

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?

If I want to do it line-by-line is is some combination from
getLine, putStr ?

Regards
Friedrich





Re: how to write a simple cat

1999-05-31 Thread Hannah Schroeter

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.

 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?

 Regards
 Friedrich

Regards, Hannah.





how to write a simple cat

1999-05-28 Thread Friedrich Dominicus

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?

Regards
Friedrich





Re: how to write a simple cat

1999-05-28 Thread David Overton

On Fri, May 28, 1999 at 04:00:27PM EST, 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?
 

Hi, 

You shouldn't need to use hugsIsEOF.  Here's one possible
implementation of a simple cat program:

module Main(main) where

import System

main::IO ()

main = 
do
args - getArgs
case args of
[] - interact id
_  - mapM_ (\f - readFile f = putStr) args


Hope this helps.


David
-- 
David Overton   Department of Computer Science  Software Engineering
MEngSc Student  The University of Melbourne, Australia
+61 3 9344 9159 http://www.cs.mu.oz.au/~dmo





Re: how to write a simple cat

1999-05-28 Thread Keith Wansbrough

module Main ( main ) where

import IO
import System

main :: IO ()
main = do args - getArgs
  s - case args of
 []- getContents
 [inF] - readFile inF
 _ - fail "Sorry, only 0 or 1 args implemented"
  putStr s


--KW 8-)
-- 
: Keith Wansbrough, MSc, BSc(Hons) (Auckland) :
: PhD Student, Computer Laboratory, University of Cambridge, England. :
:  (and recently of the University of Glasgow, Scotland. [] )   :
: Native of Antipodean Auckland, New Zealand: 174d47' E, 36d55' S.:
: http://www.cl.cam.ac.uk/users/kw217/  mailto:[EMAIL PROTECTED] :
:-: