RE: rounding in haskell

2000-02-08 Thread Frank A. Christoph

John Hughes wrote:
> Taking Ian Stark's example a little bit further,
>
>   Main> let x=6.0e-8 in (1.0,1.0+x,1.0==1.0+x)
>   (1.0,1.0,False)
>
> is a useful reminder that show isn't one-to-one.

Dunno much about FP arithmetic, but maybe there should be a primitive
showFloatExact which yields the representation itself rather than an
approximation. It might even be necessary for applications that use show* to
implement persistence.

It seems to me there is a tension between using show as a way of doing quick
and dirty pretty-printing and as a way of getting a portable representation
of data. I run across this sometimes when I forget that show :: String ->
String surrounds the input string with quotes, behavior leads me to believe
that show is really intended for the latter purpose, portability and
persistence. By that token at least it doesn't seem too unreasonable to
output an FP representation rather than an approximation for real-ish
datatypes.

--fac




RE: drop & take [was: fixing typos in Haskell-98]

2000-01-26 Thread Frank A. Christoph

Brian Boutel wrote:
> On Thursday, January 27, 2000 2:08 PM, Frank A. Christoph
> [SMTP:[EMAIL PROTECTED]] wrote:
>
> >> My preference is still (B). (A) is not *very* bad, but should really
> >> replicate (-7) "foo" be []?
> >
> >I could say: Sure, why not? replicate suffers from the same
> domain problem
> >as take/drop.
>
> This was not the point of introducing replicate to the discussion.
> The Prelude says, in a comment,
>
> -- replicate n x is a list of length n with x the value of every element
>
> and then defines replicate in terms of take.
>
> replicate:: Int -> a -> [a]
> replicate n x=  take n (repeat x)

I don't see that there is any great difference between that and the Prelude
comment describing take:

-- take n, applied to a list xs, returns the prefix of xs of length n, or xs
itself if n > length xs.

Both descriptions are equally undefined w.r.t. negative arguments.

My point is that when the behavior of replicate was described using the
equation above, I think the authors did not intend (although I admit you
would know better than me :) to define replicate in terms of the behavior of
take, whatever it happens to be, but rather in terms of a specific
mathematical function which they wrongly thought take denoted. We all agree
that take is ill-defined; replicate is ill-defined for the exact same
reason, so I would presume that _in principal_ the semantics of replicate
are also up for grabs. So I'm just saying you can't argue for a specific way
of completing take by just pointing at replicate if you want to respect the
spirit (i.e., intended meaning) and not just the letter of the Prelude.

That said, I certainly think we _should_ define the new behavior of
replicate so that it agrees with the above equation, if possible. (In other
words, I was just nitpicking. :) I agree with everything else you wrote:

--fac

> There is a clear assumption on the part of the Prelude authors
> that take behaves in a particular
> way, corresponding to the law
> length (take n xs ) === n
> but it doesn't. So even the authors of the Prelude got caught by
> take's inconsistency.
>
> While I dislike functions with a simple, obvious intended
> semantics being extended in non-obvious,
> non-simple ways, because it creates just this kind of error, I
> understand that many people are less concerned
> about it. I can live with any of the proposed definitions, but do
> suggest that incorrect statements are corrected.
>
> So, if negative values are to be allowed in take, the comment re
> replicate should say,
>
> -- if n >=0 replicate n x is a list of length n with x the value
> of every element
>
> Or, if negative values are *not* to be allowed in take, then fix
> the present code so that they are
> not allowed for any list, including [].
>
> --brian
>
>
>
>




RE: drop & take [was: fixing typos in Haskell-98]

2000-01-26 Thread Frank A. Christoph

> My preference is still (B). (A) is not *very* bad, but should really
> replicate (-7) "foo" be []?

I could say: Sure, why not? replicate suffers from the same domain problem
as take/drop.

But instead I will point out that you don't need to define replicate via
take, so, in principal, that behavior does not necessarily follow from how
we define take/drop. Of course, you might end up forcing it if insist on
some set of laws relating the two.

--fac



RE: Clean and Haskell

2000-01-13 Thread Frank A. Christoph

I wrote:
> Doug Ransom wrote:
> > It seems to me that a compiler would be an ideal candidate for writing
in a
> > functional language.  The number of times C++ compilers have given out
on me
> > indicates that C++ is not suitable for writing anything as complicated
as a
> > C++ compiler.
[...]
> It seems to me that a compiler would be an ideal candidate for being
written
> in an imperative language. The number of times GHC has been too slow and
> memory-hungry for me indicates that Haskell is not suitable for writing
> anything as general-purpose as a compiler.

which spurred some people to respond in this way:

Tommy Thorn wrote:
> That's a fairly naive remark.  I could write you a really slow and fat C++
compiler i
> C if you like. There are a number of reasons why it's too early judge.
For a
> stunning example, you should look at Niklas Rojemo's thesis about NHC.
Now there's a
> space-tight compiler (although slow).
>
> Having said all that, yes, predictable memory behavior is IMHO the biggest
problem of
> lazy language implementation these days.

which leads me to believe that some people are not careful readers, or lack
a sense of humor mixed with a healthy dose of perspective, or like to quote
others out of context, or enjoy picking on well-meaning posters who merely
like to shake the tree every once in a while. :)

Oh, and by the way, Tommy, that's a fairly naive remark. I could write you a
really fast and lean Haskell compiler in Haskell if you like. There are a
number of reasons why it's too early to judge. For a stunning example, you
should look at the GCC compiler. Now there's a fast compiler (although
space-hungry).

Having said all that, yes, correct program behavior is IMHO the biggest
problem of imperative language implementation these days.

--FAC




RE: Clean and Haskell

2000-01-13 Thread Frank A. Christoph

Doug Ransom wrote:
> I am curious.  How much faster do you think GHC would run if it were
written
> in C?  Or how much slower would a C++ compiler be if it were written in
> Haskell instead of C++?
>
> It seems to me that a compiler would be an ideal candidate for writing in
a
> functional language.  The number of times C++ compilers have given out on
me
> indicates that C++ is not suitable for writing anything as complicated as
a
> C++ compiler.

How much faster do you think C++ programs would be if C++ compilers were
written in Haskell? Or how much slower do you think Haskell programs would
be if Haskell compilers were written in C++? [Think "program optimization".]

On the flip side...

It seems to me that a compiler would be an ideal candidate for being written
in an imperative language. The number of times GHC has been too slow and
memory-hungry for me indicates that Haskell is not suitable for writing
anything as general-purpose as a compiler.

Food for thought. :) I'm in an equivocal mood tonight...

--FAC




RE: Illegal type in class constraint

2000-01-05 Thread Frank A. Christoph

My error; the problem was a kind mismatch. Sorry to bother you folks.

> -Original Message-
> From: Frank A. Christoph [mailto:[EMAIL PROTECTED]]
> Sent: Friday, December 17, 1999 11:47 AM
> To: Haskell List
> Subject: Illegal type in class constraint
> 
> 
> I have a datatype which looks like:
> 
>   data T c d f g = forall a. T ...
> 
> and I want to make it an instance of a class C:
> 
>   instance (C c, C d) => C (T c d) where ...
> 
> However, Hugs98 (newest version) gives me an error:
> 
>   Illegal type in class constraint
> 
> which I have determined does not arise from the constraint (the 
> "(...)=>" part) but from the "head" Cat (T c d), since I can 
> comment out the constraint and get the same error.
> 
> This error message is not very informative, so I'm guessing there 
> is some rule that types with locally quantified constructors must 
> be fully applied in instance heads. Is that correct? 
> Incidentally, all the arguments to T are also type functions, in 
> case it matters.
> 
> Haven't tried this on GHC yet.
> 
> --FAC



Illegal type in class constraint

2000-01-05 Thread Frank A. Christoph

I have a datatype which looks like:

  data T c d f g = forall a. T ...

and I want to make it an instance of a class C:

  instance (C c, C d) => C (T c d) where ...

However, Hugs98 (newest version) gives me an error:

  Illegal type in class constraint

which I have determined does not arise from the constraint (the "(...)=>"
part) but from the "head" Cat (T c d), since I can comment out the
constraint and get the same error.

This error message is not very informative, so I'm guessing there is some
rule that types with locally quantified constructors must be fully applied
in instance heads. Is that correct? Incidentally, all the arguments to T are
also type functions, in case it matters.

Haven't tried this on GHC yet.

--FAC



RE: Type application: a modest proposal.

1999-12-06 Thread Frank A. Christoph

I wrote:
> I think he means the application term associated with second-order lambda
> calculus' "big lambda," usually written "M [T]" or just "M T" where M is a
> value term and T is a type term, e.g., "(/\X.\x.x) Int 3".

Should be: "(/\X.\x:X.x) Int 3". (Doesn't make much sense if you don't say
what type variable your abstracting...!)

--FAC




RE: Type application: a modest proposal.

1999-12-06 Thread Frank A. Christoph

Fergus Henderson wrote:
> On 06-Dec-1999, Alex Ferguson <[EMAIL PROTECTED]> wrote:
> >
> > Now that rank-2 polymorphism seems to be part of the 'received standard'
> > (at least two implementations support 'em, and I assume they're
> a shoo-in
> > for Haskell 2), couldn't we really also do with type application?
> > It seems that ambiguity is here to stay in Haskell, and in principle
> > R2L makes the situation (at least as regards "uninferability") worse.
> > But it also provides at least a partial solution:  when one has to
> > disambiguate a subexpression, as opposed to a top-level def., in several
> > cases I've been bitten by, it would have been more concise to remove
> > the ambiguity with a type-ap, than by supplying a complete signature.
> >
> > I'd suggest a syntax for this, but I shall refrain, on account of
> > a) not having thought of one, and b) having an uneasy feeling I've
> > missed something obvious and am about to have this suggestion shot
> > down in flames.
>
> I'm not sure what you mean by type application in this context.
> Could you explain in more detail what you mean, or give some reference?

I think he means the application term associated with second-order lambda
calculus' "big lambda," usually written "M [T]" or just "M T" where M is a
value term and T is a type term, e.g., "(/\X.\x.x) Int 3".

If not, I misunderstood Alex's post too.

--FAC




RE: The Haskell compiler of my dreams...

1999-11-26 Thread Frank A. Christoph

Simon Peyton-Jones wrote:
> Third, while the things you mention are important, they are not
> at the top of the wish-list that Sven maintains for users of
> Haskell
(http://marutea.pms.informatik.uni-muenchen.de/wishlist/index.html)

Does that mean that (to borrow from the GHC docs) "smaller, faster,
stingier" are acceptable items for the wishlist? That possibility had never
occurred to me.

--FAC



RE: A datatype for the text editor buffer?

1999-11-08 Thread Frank A. Christoph

I wrote:
> I have never seen anyone use the technique in any distributed Haskell
code.
> Gerard Huet wrote the article that appeared in JFP, and I believe he
> remarked that they had used the technique to represent ASTs in a
structural
> editor (perhaps in the Coq distribution?).

Sorry, let me improve this:

Huet said they had used the technique to represent _positions_ in ASTs in a
structural editor, and to efficiently implement _editing without imperative
constructs_. This is possible because the navigation functions on a
Zipper-style first-order language are (with some exceptions) mostly constant
order, and so are the modification functions. You don't have to copy the
whole tree to modify it, since you can explicitly manipulate the context of
just the expression which is going to be modified.

Also, I didn't mention that Coq is (now) written in Ocaml.

--FAC




RE: A datatype for the text editor buffer?

1999-11-08 Thread Frank A. Christoph

> > The Zipper technique is the generalization
> > of this idea to arbitrary algebraic datatypes; it can be generalized
to
> > higher-order data too (continuations).

I was too optimistic when I wrote this; someone actually e-mailed me asking
for a fuller explanation after I posted this, but I had to take this claim
back. (Unfortunately, I didn't correct myself in public.) At the time I had
been fooling around with the idea, but never figured out exactly how to
implement it.

> Is there some code around that illustrates the use of Zippers?  They
> sound very interesting.

I have never seen anyone use the technique in any distributed Haskell code.
Gerard Huet wrote the article that appeared in JFP, and I believe he
remarked that they had used the technique to represent ASTs in a structural
editor (perhaps in the Coq distribution?).

--FAC




RE: Barmy idea for the day: Type annotations in export lists

1999-10-13 Thread Frank A. Christoph

> It would be nice to be able to say
>module Shape(
>   Shape,
>   Square :: Int -> Shape,
>   RotateDegrees :: Int -> Shape -> Shape,
>   ...
>   ) where . . .
> Ideally one would want to be able to have instance declarations as well.
> This would mean that someone using the Shape module would only have
> to look at the top of the file.  Of course such information can be
> added in comments, but then there is no way of checking it.

I suggested this (module interfaces) for Haskell 98, but the consensus was
that it involved too many design decisions to include immediately. However,
many people seem to want this, so I feel sure it will make it into Haskell-2
in some form. Maybe now is a good time to consider the design issues...? I
think Mark Jones enumerated most of them back then. Is the Haskell 98
discussion board that was on John Hughes' page archived anywhere?

--FAC







RE: [haskell] list reorg

1999-10-12 Thread Frank A. Christoph

Simon Marlow wrote:
> Here's my proposal:
>
>   - haskell-announce (v. low volume)
>
>   - haskell-chat (high volume, anything vaguely related to
> Haskell is acceptable)
>
>   - haskell-questions (questions about the use of the language,
> maybe haskell-help or haskell-users)
>
>   - haskell-2 (discussions related to changes/extensions to
> the language)
>
>   - haskell (general discussion list, anything not covered above)

I like this setup except I don't see a need to distinguish between
"haskell-chat" and "haskell".

Also, I have been thinking about the comp.lang.haskell proposal and, spam
problems aside, I am not opposed to it, provided that people can participate
via email as well as Usenet; this must be possible, since the ML list is
doing it. (Indeed, I didn't realize that the ML list was identical to
comp.lang.ml until a few months after I joined it!)

--FAC







RE: The Haskell mailing list

1999-10-08 Thread Frank A. Christoph

> Traffic on the Haskell mailing list has jumped dramatically of late.
[...]
> So we can decide to do one of two things:
>
> 1.  Try to keep the Haskell mailing list as a low-traffic list, to which
>   many, many people subscribe.  Under this model, one might *start*
>   a discussion on the Haskell list; but after a few exchanges, move the
>   discussion to comp.lang.functional, or perhaps a high-traffic Haskell
>   list (haskell-discuss?).  Rather like coastguard radio, where
> one starts
>   on Channel 16, but moves to another channel to converse.
>
> 2.  Accept (even rejoice) that the Haskell mailing list is becomming a
>   high traffic list, and accept that people will drop off.  I,
> for one, will
>   probably drop off soon. Maybe another low-traffic list will start.

I like 1, but much prefer creating another mailing list to moving lengthy
discussions to comp.lang.functional since a) I can't read newsgroups from
all my accounts, b) c.l.f is already overloaded.

Another option is to create a low-bandwidth list called haskell-announce and
keep this group the way it is.

Yet another option: Since most of the heated discussions that occur on this
list pertain to proposed extensions or changes to Haskell, we can create a
"haskell2" list, and ask people to post that sort of speculative stuff
there, leaving this list for discussion of Haskell98 as it stands.

--FAC









RE: OO in Haskell

1999-10-06 Thread Frank A. Christoph

Kevin Atkinson wrote:
> Ok here is my partial list.
>
> - True ad-doc polymorphism
> - Built in dynamic typing system.
> - State Encapsulation
> - A solution to the abilities arising from multi parameter type classes.
> - Syntactic sugar for supporting OO programming styles

What is the significance of dynamic typing being "built in"?

What do you mean by "state encapsulation"?

What sort of syntactic sugar is it that you want?

--FAC







RE: CPP is not part of Haskell

1999-10-05 Thread Frank A. Christoph

Manuel Chakravarty wrote:
> Jan Skibinski <[EMAIL PROTECTED]> wrote,
>
> > If a good pre-processor is still a valid option, would not
> > something similar to Camlp4 be better than the plain CPP?
> >
> > Camlp4 ===> http://pauillac.inria.fr/camlp4/
> >
> > "Camlp4 is a Pre-Processor-Pretty-Printer for Objective Caml.
> > It offers syntactic tools (parsers, extensible grammars), the
> > ability to extend the concrete syntax of Objective Caml
> > (quotations, syntax extensions), and to redefine it from
> > scratch."
> >
> > If such a Haskell-specific tool existed and had the
> > ability to support any syntactic extensions to Haskell
> > then people would not have to worry too much about
> > syntactic incompatibilities, would they?
>
> The problem is that a pre-processor adds a new level of
> semantic complexity to the language - so if we can do
> without it, we'll definitely make our lives simpler.
>
> Besides, one nice property of Haskell is its relatively
> (compared to other languages) precise semantic definition
> (ie, the translation to the Haskell kernel).  A
> pre-processor wouldn't fit nicely in here, I suppose.

Camlp4 is not part of the language definition for Ocaml, and I don't know if
Jan is necessarily advocating that an analogue would need to be part of the
one for Haskell. If you don't mind parsing your source twice, a Camlp4-like
processor can just output plain old Haskell. The actual Camlp4 can also
output a binary form of Ocaml's ASTs, and a special switch on the compiler
(there is only one implementation of Ocaml! :) reads it in directly and
avoids reparsing.

--FAC







RE: Where is "Server Side Scripting" code?

1999-10-05 Thread Frank A. Christoph

> Jan Skibinski:
> > What is available from haskell.org are two much outdated versions of CGI
> > library: one by Erik himself and one modified (and adopted to
> Haskell 98)
> > by Sven Panne. By outdated I mean that they both are based on Erik's
> > earlier work and much predate the refined and simplified concepts,
> > quite nicely described in the paper.
>
> I encountered this same situation several months ago;  I asked around,
> but I'm no further forward, I'm afraid.

Erik told me a few weeks ago that he is planning to update the package.
Unfortunately I haven't heard from him in a while, so I assume he is away on
a trip or something (ICFP?).

Meanwhile I took his old version, updated it to H98, fixed some bugs, added
a few things to it myself ("ugly-printing", since the Pretty module is
unbearably slow under Hugs; support for preformatted text; support for
"unclosed" tags like HRULE), plus I folded in a little snippet of Jan's code
for escaping HTML characters. (In other words, I have mostly duplicated
Jan's work. ;) I kept Erik's file structure, though.

I will send it to anyone who's interested, pending Erik's re-release.

--FAC







RE: CPP is not part of Haskell

1999-10-04 Thread Frank A. Christoph

> > I'm not sure I agree with this.  Keith Wansbrough has an interesting
> > paper that identifies the ways in which a macro processor can
> > do thing that ordinary functions can't.   
> 
> Is this paper available somewhere?

Keith Wansbrough (1999). Macros and Preprocessing in Haskell. Unpublished. 

directly: http://www.cl.cam.ac.uk/users/kw217/research/misc/hspp-hw99.ps.gz
indirectly: http://www.cl.cam.ac.uk/users/kw217/research/papers.html

--FAC







RE: advice wanted on GUI design patterns

1999-10-01 Thread Frank A. Christoph

> > I found this bold statement from their top page amusing:
> >
> >   If you want to build robust, scalable, complex _and yet exciting_
software
> >   then you need to use pure object-oriented programming techniques.
> >   [emphasis mine]
>
> Personally, I am a strong advocate of dynamic, rather than static, typing
in
> a programming language. In my experience dynamic type sytems do not
decrease
> the overall reliability of a system but, if anything, they improve it. In
> addition, the dynamic typing in Smalltalk allows the software creation
> process to be more, well ... dynamic. To my mind it's more enjoyable
because
> of this (and who say's we shouldn't enjoy building software).
> Anyway, there are enough USENET debates of this dynamic vs static
> debate so I won't bring it up further here.

You are quite right (about usenet debates). I deserve some ribbing over that
post and now I rather regret posting it. It was mostly the wording on that
web page, not the content, which raised my ire and unfortunately it got the
better of me.

You have my humble apologies.

--FC







RE: advice wanted on GUI design patterns

1999-09-29 Thread Frank A. Christoph

> Just before everyone starts writing MVC (model-view-controller)
> GUIs, you should be aware that there is a later development called
> MVP (model-view-presenter), which decouples the components
> even more.
>
> Main Dolphin site:
>
http://www.object-arts.com

Thanks for the link.

I found this bold statement from their top page amusing:

  If you want to build robust, scalable, complex _and yet exciting_ software
  then you need to use pure object-oriented programming techniques.
  [emphasis mine]

I've always thought Haskell applications were robust, scalable and sometimes
complex, but it is true that there was always some excitement lacking...
("My applications are so dull; they never have run-time type errors... Oh, I
do so long for that familiar old `message not understood.' Hm, maybe if I
had used pure object-oriented programming techniques...!")

And then a more foreboding warning:

  If you've not used Smalltalk before then you're in for a new experience.
  Take care, though. The language and environment are so interactive
  and engrossing that you may find that in no time you become addicted.
  You have been warned.

Jeepers!

--FC

P.S.: With tongue in cheek. I have anything against Smalltalk or Object
Arts...







RE: Where would one use Maybe as a monad?

1999-09-28 Thread Frank A. Christoph

> > However, I note that Maybe is an instance of Monad.  What for?
>
> Someone, I think at Glasgow, has a web page called something
> like "What the hell are monads?", which I thought gave a pretty
> good practical description of them.  I can't remember who
> made this page, though.  Anybody know who/where it was?
> It's been mentioned on this list in the past couple of
> months, I think.

Noel Winstanley. http://www.dcs.gla.ac.uk/~nww/Monad.html

You can find this and other information at the Haskell Bookshelf at
http://haskell.org.

Many of the Haskell designers also have interesting and useful papers
available from their own web pages. You can find those links, for example,
in the online version of the Haskell 98 Report,
http://haskell.cs.yale.edu/onlinereport/.

--FC







Qualified identifiers (was: RE: What *I* thinks Haskell Needs.)

1999-09-27 Thread Frank A. Christoph

> For bigger things which
> you want to identify, you can either use qualified module identifiers, or
> Haskell's type classes which at least let you establish and codify a
> motivation for using the same name for distinct things (namely, that their
> types are equivalent under a particular relation).

BTW, since I mentioned it, let me get on my hobby horse and implore other
Haskell programmers to _please_ make more use of the qualified ID syntax!
Haskell has had this feature for quite some time now, but I hardly ever see
it used...

Especially in modules that import a lot of other modules, it's

* easier to _recognize_ an identifier if it's prefixed by a module ID rather
than look through all the imported modules, and

* easier to _modify_ a module if all you need to do to pull in a new value
is to use it, rather than scrolling up, and adding it to the list of
identifiers in something like "import M (...)".

This is standard practice in both SML and Ocaml. (In fact, I would rather
not have to declare things like "import qualified M" at all...)

If you have a long module name, declare an alias:

  import qualified LongModuleName as LMN

BTW, another advantage of this syntax is that identifiers within their own
defining module get shorter, and consequently it gets easier to read. For
example, don't define "addToFM"; define "addTo" and then do "import
FiniteMap as FM". Sometimes this means having to hide Prelude identifiers
and qualify them at use (as it would be with "lookupFM" in GHC's FiniteMap
module) but is that such a great price to pay...?

Please. Pretty please? Pretty please with sugar on top?

--FC

P.S. Except infix combinators. These are ugly when you qualify them.







RE: What *I* thinks Haskell Needs.

1999-09-27 Thread Frank A. Christoph

> > I find that if you make liberal use of higher-order constructs and
> > modularize your code, then the need to do explicit binding is
> not so much of
> > a problem. Then again, I am the sort of person who uses "let"
> and "where"
> > whenever he can to name subexpressions as well...
>
> But the point is I would like the type system to AUTOMATICALLY do this
> for me so that I don't have to memorize/lookup a bunch of higher order
> functions.  True ONCE you know them all they are not difficult to use
> but to a new programmer all these (seemly unnecessary) high functions
> can make doing the simplest task quite difficult.  So the new programmer
> will just use the do

Doesn't it also make it easier on new users that things with different
semantics have different names? It seems like true ad hoc overloading would
only make things more confusing; certainly the error messages would become
more difficult to understand.

It would eliminate the need to think up new names in some circumstances, but
if you compare the amount of time spent in doing that when you write a
program, to the amount of time you might spend trying to figure out why your
program won't compile, or worse, compiles but runs incorrectly (I have a
hard enough time, sometimes, figuring out what the type of something is in
the presence of functors and MPTC!) Experiential reports and empirical data
would be valuable here.

> This is why I belive in true adhoc overloading.
>
> 1) so that you don't have to make up names just reuse the old ones
> 2) make using standard library functions easier to use because there
> will be a lot fewer names to lookup/memorize.

1) For intermediate values which are not so important, you can get around
inventing new names by using scoping and shadowing. For bigger things which
you want to identify, you can either use qualified module identifiers, or
Haskell's type classes which at least let you establish and codify a
motivation for using the same name for distinct things (namely, that their
types are equivalent under a particular relation). That's already four
mechanisms for dealing with overloading.

2) It would also be useful if documentation were easier to access and use
(which has been a recent topic).

I must admit that I don't like the idea of determining a value based on its
type, at least in a language like Haskell. For me, functional programming is
about how to write programs combinatorially, and justifying your hypotheses
by encoding their proofs; so a type is something that ought to be uniquely
derivable from a value, not the other way around. Haskell's class system
already goes too far against this idea for my taste.

I know that some people do not feel this way, however.

--FC







RE: What *I* thinks Haskell Needs.

1999-09-27 Thread Frank A. Christoph

Oops, I left out the type context:

> liftM2' :: (Monad m) => (a -> b -> m c) -> (m a -> m b -> m c)
> liftM2' proc m1 m2 = do
>   v1 <- m1
>   v2 <- m2
>   proc v1 v2

Oh, and here is a nicer definition:

  import Monad

  liftM2' :: (Monad m) => (a -> b -> m c) -> (m a -> m b -> m c)
  liftM2' proc m1 m2 = join $ liftM2 proc m1 m2

Maybe jLiftM2 is a better name?

--FC







RE: What *I* thinks Haskell Needs.

1999-09-27 Thread Frank A. Christoph

> Here is a laundry list of things I think Haskell still needs.  By
> Haskell here I mean Haskell plus extension that are found in both hugs
> and ghc.
...
> 4) Being able to write
>   do a <- getLine
>  b <- getLine
>  proc a b
> as
>   proc getLine getLine
> and the like.  I don't know the number of times that I get REALLY sick
> of having to explicitly bind everything to a variable.  Monads do a very
> good job of supporting imperative style.  Now lets make them less
> tedious to use.

You could define proc':

proc' act1 act2 = do
  v1 <- act1
  v2 <- act2
  proc v1 v2

so you can write:

 proc' getLine getLine

When proc returns a value rather than a computation, i.e., proc :: a -> b ->
c, and c is not monadic, then you can just write Monad.liftM2 proc getLine
getLine.

You could define a higher-order version of proc' above in the same vein:

liftM2' :: (a -> b -> m c) -> (m a -> m b -> m c)
liftM2' proc m1 m2 = do
  v1 <- m1
  v2 <- m2
  proc v1 v2

In simpler cases where proc takes only one argument, you can avoid thinking
up new names by currying:

  getLine >>= proc

I find that if you make liberal use of higher-order constructs and
modularize your code, then the need to do explicit binding is not so much of
a problem. Then again, I am the sort of person who uses "let" and "where"
whenever he can to name subexpressions as well...

--FC







RE: Non-strictness vs. laziness (was RE: Sisal)

1999-09-24 Thread Frank A. Christoph

Bjorn Lisper wrote:
> >Joe Fasel wrote:
> >> Actually, I think we were originally thinking of laziness, rather
> >> than nonstrictness, and weren't considering languages like Id as
> >> part of our domain, but Arvind and Nikhil (quite correctly) convinced
> >> us that the semantic distinction of strictness versus nonstrictness
> >> should be our concern, rather than the operational notions of
> >> eagerness and laziness.
>
> "Frank A. Christoph" <[EMAIL PROTECTED]>:
> >Please elucidate. Where does this difference become important?
> What impact
> >did it have on the language?
>
> It is definitely important in parallel processing, where you may want to
> spawn off activities speculatively, to utilize idle processors, and kill
off
> these activities later if it is discovered that their results are not
> needed. This yields nonstrict behaviour if implemented correctly,
> but it is not lazy.

Ah, right. Someone mentioned just recently (I forget who---sorry) that
nothing in the Report forces a Haskell implementation to use call-by-need. I
guess this is a manifestation of the change of direction, from laziness to
non-strictness...?

There is a broader sense of the term "lazy" which includes not only
call-by-need but also call-by-name. Since Joe wrote "eagerness and
laziness", terms which are apparently in opposition, I assumed this was the
meaning he intended (since CBV and CBName are dual, but the relationship
between CBV and CBNeed is not so neat). I actually was more interested in
whether there is a practical distinction between a call-by-name calculus and
a calculus whose lambda-abstractions are modelled by non-strict functions.

--FC






Non-strictness vs. laziness (was RE: Sisal)

1999-09-24 Thread Frank A. Christoph

Joe Fasel wrote:
> Actually, I think we were originally thinking of laziness, rather
> than nonstrictness, and weren't considering languages like Id as
> part of our domain, but Arvind and Nikhil (quite correctly) convinced
> us that the semantic distinction of strictness versus nonstrictness
> should be our concern, rather than the operational notions of
> eagerness and laziness.

Please elucidate. Where does this difference become important? What impact
did it have on the language?

--FC






My Humble Haskell Wish: concatSep

1999-09-08 Thread Frank A. Christoph

I have a humble wish for the Wish List.

I wish this function was in the Prelude or standard library:

  concatSep :: [a] -> [[a]] -> [a]

with semantics

  concatSep _ [] = []
  concatSep _ [xs] = [xs]
  concatSep sep (xs:xss) = xs ++ sep ++ concatSep sep xss

I use it all the time. Unfortunately, it doesn't even appear in GHC's
non-standard libraries (although there is an analogue in Pretty).

--FC






RE: Is their a *good* online tutorial and reference for Haskell?

1999-08-11 Thread Frank A. Christoph

> | Is this why the PDF version of the Haskell report looks so 
> strange? On my
> | system (Win98 and Acrobat Reader 4.0) it looks like the baseline
> | oscillates up and down between each letter. I find it very difficult to
> | read.
> 
> I made a pdf version of the Haskell report using pdflatex; fans of
> pdf can obtain a copy from http://www.cse.ogi.edu/~mpj/h98.pdf.
> This version of the report includes hyperlinks and bookmarks, and
> looks *much* better on screen than the version derived from Postscript.
> It's even (slightly) smaller ... what a deal!

Thanks, Mark. This fixes the problem above and looks fantastic.

--FC






RE: Is their a *good* online tutorial and reference for Haskell?

1999-08-11 Thread Frank A. Christoph

> These fonts are especially recommended for use with pdfTeX.
> In fact, for
> PDF output one should not even consider applying the bitmap fonts for they
> produce terrible results, whether generated with pdfTeX or with the
> Distiller program.

Is this why the PDF version of the Haskell report looks so strange? On my
system (Win98 and Acrobat Reader 4.0) it looks like the baseline oscillates
up and down between each letter. I find it very difficult to read. I've seen
the same effect on other PDF-converted technical reports which were
obviously produced with TeX/LaTeX. With Acrobat Reader 3.0 on Solaris, I
don't see the same effect, although the lettering looks very cruddy (even
with anti-aliasing on) and is equally hard to read.

I had been meaning to mention these facts earlier... It would be nice if
someone could regenerate the Reports.

--FC






RE: Is their a *good* online tutorial and reference for Haskell?

1999-08-10 Thread Frank A. Christoph

> Then an Anonymous Coward replyed:
>
> Is their a good online tutorial and reference for Haskell? Last time I
> looked all I could find were pointers to books and links to Amazon.Com. Oh
> yes, and some moldy academic papers in postscript format. I think it would
> behoove those in the communities of less well know languages to provide
> good online instruction and reference material. I'm not going to pop 60
> bucks to learn another language that may or may not meet my needs. Try
> before you buy.

Moldy? I started learning Haskell by reading those papers, and found them
very useful. Most of them are out of date now (and some of them were out of
date then) but it looks like some, at least, are being updated. For example,
at

http://haskell.org/tutorial/

("A Gentle Introduction To Haskell, Version 1.4" by Hudak, Peterson and
Fasel) it says that

> We are working on a version 98 of this tutorial, expanded and updated for
Haskell 98. This new
> version isn't complete yet but is probably a better reference than this
one.

Of course there can never be enough tutorials or documentation for a
programming language, but I don't think Haskell is all that thin on free
learning materials. There is tons of stuff to be found on haskell.org,
certainly enough to get a feel for the language and to motivate someone to
shell out some bucks on a book if it interests them.

--FC






RE: Again: Referential Equality

1999-07-28 Thread Frank A. Christoph

Fergus wrote:
> On 27-Jul-1999, Simon Marlow <[EMAIL PROTECTED]> wrote:
> > > > I would like to have a comparison instruction that compares
> the internal
> > > > reference of two objects.
> > > > Let's call it "req".
> > > >
> > > > req :: a -> a -> Bool
> > >
> > > By coincidence, I was just looking at GHC's documentation on
> > > stable names and pointers, and it seems relevant here. [...]
> > > Something like this might do the job for you:
> > >
> > > req a b = unsafePerformIO $ do
> > >a' <- makeStableName a
> > >b' <- makeStableName b
> > >return (a' == b')
> >
> > That's exactly what to use in a situation like this.
>
> I disagree.  `makeStableName' may be the right thing to use,
> but the above code is not quite the right way of using it.
> Instead the call to unsafePerformIO should be propagated outwards --
> see my other post.

Your point is well taken, but he was after all asking for an req with an
unsound type. Caveat user.

> > ... if you intend to encapsulate your use of pointer equality in a
> > "safe" abstraction, say a memo table, then use of unsafePerformIO is
> > entirely justified.  The req function above is of course an "unsafe"
> > abstraction, because it exposes the representation of a and b.
>
> Yes, the use of `unsafePerformIO' is justified in such cases.
> But the call to `unsafePerformIO' should be from the code defining the
> safe abstraction.  If you put the call to `unsafePerformIO' in an
> unsafe primitive such as `req', then when your code is compiled with
> some optimizing compiler which assumes that functions are referentially
> transparent the resulting executable may dump core.

Dump core? I would expect the compiler to disable any such optimizations
when it sees an unsafePerformIO.

What does GHC do?

--FC






RE: Again: Referential Equality

1999-07-28 Thread Frank A. Christoph

> So the two conditions
> if  a `eq` b  then F(a) `eq` F(b)
> if  a `req` b  then G(a) `req` G(b)
> will only lead to different classes of functions (homomorphisms with
> respect to different properties). The latter will in math more correspond
> to consider all underlying set functions, whereas in the former case one
> restraints at preserving certain semantic structure.
>
> So I think one should not bother too much about breaking referential
> transparency when allowing access to the underlying runtime covers. On the
> contrary, it seems that this exactly what one should expect to happen.

I would not be so gung-ho about breaking referential transparency. While I
agree that it is convenient in specific cases to have a language that
doesn't obey referential transparency, and just use a different, more
specialized theory for reasoning about programs, it seems like that strategy
would force one to deal with either one complex, monolithic theory, or a
multiplicity of similar smaller theories.

The way Haskell employs monads, we can define what amounts to a
domain-specific sublanguage which maybe isn't referentially transparent, and
then translate propositions about programs in the sublanguage into more
familiar propositions about Haskell programs which are referentially
transparent. So Haskell functions as a universal language to express
domain-specific language denotations in. That was the whole point of
introducing monads in the first place, I think: compositional denotational
semantics.

So, why would you want to break referential transparency when you've gone to
all the above trouble to preserve it already?

--FC






RE: Again: Referential Equality

1999-07-27 Thread Frank A. Christoph

> I would like to have a comparison instruction that compares the internal
> reference of two objects.
> Let's call it "req".
>
> req :: a -> a -> Bool

By coincidence, I was just looking at GHC's documentation on stable names
and pointers, and it seems relevant here.

http://research.microsoft.com/users/t-simonm/ghc/Docs/latest/libraries/libs-
14.html

Something like this might do the job for you:

req a b = unsafePerformIO $ do
   a' <- makeStableName a
   b' <- makeStableName b
   return (a' == b')

--FC






RE: Deriving Enum

1999-07-12 Thread Frank A. Christoph

> > > Miranda has something called diagonalizing list 
> > comprehensions if I recall
> > > correctly. I think you would write:
> > > 
> > > [(a,b) // a <- [1..], b <-[1..]]
> > > 
> > > and the resulting list would be
> > > 
> > > [(1,1), (1,2), (2,1) ...]
> > 
> > Haskell has this too.  :) The syntax is almost the same:
> > 
> > [(a,b) | a <- [1..], b <- [1..]]
> > 
> > --FC
> >
> 
> No, your Haskell code will evaluate to: [(1,1), (1,2), (1,3), 
> ...]. Try it.
> You'll never reach (2,1). Diagonalizing list comprehensions traverse the
> matrix in diagonals. 

Sorry, I didn't notice this was supposed to be "diagonalizing"...

--FC






RE: second rank polymorphism

1999-07-08 Thread Frank A. Christoph

I wrote:
> For example, we know just from the fact that
> concat : Forall a. a -> a, that
>
>   \xs.map A B f (concat A xs) = \xs. concat B (map A B f xs)
>
> where map : forall a. forall b. A -> B -> ([A] -> [B]). Here the
> endofunctor in question is the list functor, [].

Oops, I really screwed this up.

First, I wrote the wrong type for concat:

  concat : forall a. [[a]] -> [a]

Second, that equation is not even well-typed. I meant:

  \xs. map A B f (concat A xs) = \xs. concat B (map [A] [B] (map A B f) xs)

BTW, there is no significance to the fact that I kept switching between
"Forall" and "forall"...

Maybe I should just leave the category theory to Hans...!

--FC






RE: second rank polymorphism

1999-07-08 Thread Frank A. Christoph

Let me take a shot at this.

Jan Brosius writes:
> Now I have some difficulty to follow. If I write
>
> id :: a -> a
>
> then I thought it meant " id is a "function" from type a to type a " ; in
> logic this is completely equivalent with (since  a is a variable ):
> " forall a ( id is a function from type a to type a) "
> But then I immediately get a problem, indeed since id is a
> function from set
> a into set a then I have
>id is a subset from set aXa (the product of a with a)
> Choose a set b such that "a intersection b = empty" then
>id is subset of aXa and subset of bXb
> which is a contradiction. So id is not a function but one can define it as
> id = \x -> x that is an untypable lambda-function.

First, typeability (sp?) is not a property you can define in a vaccuum; you
have to specify typeability with respect to a set of axioms. In a
simply-typed lambda-calculus, the best you can do is to split id into a
collection of functions, one for each type. If it's a Church-style calculus,
\x.x is not even a well-formed term, since it lacks a type for its domain.
If it's Curry-style, I think you need to supplement the term with a type
assignment; there is no way to quantify a type in simply-typed
lambda-calculus, but you can still give it a type A -> A, for any A you
choose.

In SOLC (second-order lambda-calculus), you would not define it as simply
\x. x, but rather
/\X.\x.x, which can be assigned the type Pi(X).X->X, so it is certainly
typeable in that system.

> A way out of it is to write id(a) :: a -> a ; then I can really say that
> forall a ( id(a) is a function from type (or set) a into (or to) type a).

Yes, that is how you express it in SOLC: id = /\X.\x.x : Forall X. X -> X.

> And forall x forall a (id(a) x = x) which is completely equivalent with
> forall x forall a (id(a) x = x).

Be careful; you are quantifying over two different domains here. a is a
collection of x's. If you include them in the same domain, then I think you
run into size problems.

> I am very confident that you cannot go around the rule:
>  forall a forall b ( T(a,b)) equivalent with forall b forall a
(T(a,b)).
>
> So I think, before I can proceed any further in learning I invite you to
> phrase exactly what one means with
>id :: a -> a ?

It means that id cannot observe (read: destructure) its argument.

The way I know to model this is in category theory: if h : forall A. A -> A,
then h is a natural isomophism from and to the identity functor I:C=>C on
the category C modelling your calculus. (BTW, category theory completely
separates the domains of terms and types, so it is easier to avoid size
problems.) In this case, saying that h is a natural isomorphism means that
for each term f:A->B, \a.f (h A a) = \a.h B (f a). This seems natural enough
(excuse the pun) if h = id, but what is really striking about it is that
this holds for _any_ definition of h, i.e., it is a property that can be
inferred solely from the typing. For example, we know just from the fact
that concat : Forall a. a -> a, that

  \xs.map A B f (concat A xs) = \xs. concat B (map A B f xs)

where map : forall a. forall b. A -> B -> ([A] -> [B]). Here the endofunctor
in question is the list functor, []. This idea is often called "theorems for
free", since they are independent of the definition; things like the
equation above can be significant language optimizations.

In fact, id : forall A. A -> A means a little more than naturality: id has
to have the same implementation at each type A, which is not true in general
of all things that can be denoted by a natural transformation. But in
"vanilla" SOLC, I think, all the terms that denote natural transformations
obey this property. In Haskell, though, you could write:

class Id a where
  id :: a -> a

instance Id Int where
  id x = x + 0

etc., so that the instance at each type uses a different algorithm. For the
identity function, no one would do this of course because it is clearly
_parametrically_ polymorphic. Anyway, the type for this id is not quantified
the same way as it is for the parametric version, because the implementation
can depend on the particular type. You can't do this in SOLC, since to use
/\-abstraction, the type variable A in /\A.x must not appear in the
environment of x. That's why you can't write /\A.x if x:A.

(I wrote vanilla SOLC above, because I don't know if this is true for some
extensions of SOLC, in particular extensions with subtyping or bounded
quantification, but also the more general calculus where you can quantify
over type constructors. Maybe someone else knows?)

> > > I have already read all available online documentation.
> > > In logic one has: forall x forall y = forall y forall x.
> >
> > This is not the case in the second-order lambda calculus, because the
> > order of the type lambdas is clearly significant:
> >
> > (.) :: \/a. \/b. \/c. (a->b) -> (b->c) -> (a->c)
> >
> > is clearly different from
> >
> > (.') :: \/c \/b. \/a. (a-

RE: A datatype for the text editor buffer?

1999-07-07 Thread Frank A. Christoph

Peter Hancock wrote:
> > "Marcin" == Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> writes:
>
> > What do you think would be the best representation of the buffer for
> > such a crazy idea as a text editor in Haskell?
>
> I don't think its crazy.  I thought that one could start with
> something simple, like a "before" list and an "after list".  Sometime
> ago, there was an article by Bernard Sufrin, which specied a simple
> editor various derivatives of which were in use in Oxford over a
> decade ago.  If I recall the article accurately, it was so
> clearly written that
> you could more or less just transcribe it into a functional program.
> Perhaps one can find it from
>   http://www.comlab.ox.ac.uk/oucl/people/bernard.sufrin.html

Also check this one out:

Simon P. Booth, and Simon B. Jones "A screen editor written in the Miranda
functional programming language" ,Technical report TR-116, Department of
Computing Science and Mathematics, University of Stirling, February 1994.

You can find it at:

  ftp://ftp.cs.stir.ac.uk/pub/tr/cs/1994/TR116.ps.Z

I think that they use the "before"/"after" approach too. (BTW, is this what
is commonly called a "difference list"?) They reported rather poor
performance, though.

Incidentally, the "before"/"after" list approach is actually a special case
of the "Zipper" (I prefer to call them context-enriched types), which
someone mentioned in an earlier post: the "before" part is the context for
the "after" part, which is the focus, and, sure enough, the context has been
turned inside-out like a glove. It just happens that for (vanilla) lists the
context is isomorphic to a list. The Zipper technique is the generalization
of this idea to arbitrary algebraic datatypes; it can be generalized to
higher-order data too (continuations).

--FC






RE: Lambdaman GIF

1999-06-23 Thread Frank A. Christoph

> Does anyone have a GIF of (I think Phil Wadler's) Lambda-man? I
> mean the one that appeared with its friend the chip on the old
> FPCA proceedings?

Let me take a wild guess and say that it's the one at the home page of
Glasgow's FP department.

http://www.dcs.gla.ac.uk/fp/

--FC






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

RE: Language Feature Request: String Evaluation

1999-06-09 Thread Frank A. Christoph

> In principle I can do this, but:
> 1. how do I hide the import of show String to replace it w/ my own?
> 2. If I do replce show String what else will break?
> 3. If instead I define an eshow function that strips "", how do I minimize
> the perforamnce hit of quote stripping?
> 4. If I want to share my code, I have to share both the actual codebase as
> well as the preprocessor code.  This seems like sucha  basic language
> syntax issue that I shouldn't have to worry about which version of haskell
> your collaborators are running.  Everyone writing their own preprocessor
> will severely balkanize the language.

Hm, it seems to me that that is the cost of being a maverick.

> 5. How does the use of this pre-processor interact w/ tools like Derive
> and PolyP which are also implemented as preprocessors?
>
> That being said, I would be happy to take a shot at HacWrite if it had a
> shot of becoming part of the language definition (or if it was a standard
> part of the various haskell distributions: ghc, hugs, hbc,etc.) and if
> Magnus would allow it.
>
> Is there a good lanugage reason to object to this feature?  It seems like
> a no brainer imprpovement.

(Allow me to play devil's advocate.)

Not everyone uses Haskell to do web page processing or text processing, and
Haskell already has too much syntactic sugar. I don't like your notion of
changing the semantics of Show String, and I don't like the implicit show
coercions for variables that get substituted into a string. (Whenever
coercions get to be a pain, my instinct is to hide them in the plumbing of a
set of combinators.) Preprocessing introduces another stage into the
compilation process, and makes it that much more difficult to understand a
program; interaction between preprocessors can be tricky (as you pointed
out).

--FC






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






Strings in Perl

1999-05-21 Thread Frank A. Christoph

I wrote:
> After all, the world's most famous text-processing
> language, Perl,represents strings as character lists too.

I thought I had read this somewhere, for example O'Reilly's "camel" book,
but I can't find the place, and Carl Witty assures me that Perl represents
strings internally in the usual way, as arrays. In other words, I am
probably mistaken.

Sorry for the confusion.

--FC






RE: View on true ad-hoc overloading.

1999-05-20 Thread Frank A. Christoph

> What would be gained by allowing ad hoc overloading? If
> operations on different types have similar meaning
> there is a case for defining a new class. If you have existing
> different functions with similar names you can
> qualify them to avoid the ambiguity. When else would you want
> this feature?

I'm not at all sure whether I'm in favor of this kind of overloading. It's a
difficult issue. However, it's used all the time in mathematical text, and
Haskell goes a long way to make a program look like conventional
mathematical syntax (function clauses, list comprehensions, etc.), so one
might argue, why not allow overloading as well? That said, I'm leary of
identifier overloading because it can be used in ways that end up assigning
it a semantic significance, and in these cases I think type classes should
be used instead. If overloading could be restricted so that it can't be used
for, for example, hiding the type or denotation of a variable, and only to
lessen the burden of finding distinct names for things, then I think I would
be in favor of it. For example, we generally write + for the coproduct in
any category, so "this is a coproduct => write it as +", but we don't reason
in the other direction, i.e., "this operator is written + => I know it is a
coproduct." The point is that the notation should reinforce, but not
influence, the semantics.

--FC






RE: Proposal: Substring library for Haskell

1999-05-20 Thread Frank A. Christoph


> > I would welcome either. However, there is a huge body of code that
> > assumes strings are lists of chars.
>
> Yes, obviously... this is for new programs (which people aren't writing
> because of Haskell's inefficiency in dealing with strings).

While I think Haskell should also support primitive random-access strings,
String as [Char] is not all that inefficient for many purposes, thanks to
laziness. After all, the world's most famous text-processing language, Perl,
represents strings as character lists too. And, I don't agree with the claim
that strings are mostly accessed in a random-access way. Anyone who needs to
be looking into the middle of a string all the time is either using the
wrong data structure, or is doing some kind of a parsing, which is usually a
linear process anyway. However, since UNIX and other applications tend to
throw around lots of structured data using strings almost exclusively, it is
still good to have array-like strings.

--FC






The compile-time rules hack

1999-05-10 Thread Frank A. Christoph

David Barton wrote:
>
> What began with a fairly limited, and practical, suggestion on Simon's
> part to assist the compiler with optimizations and transformations
> that are valid in some cases and not in others has blossomed into a
> search for a full logical language, with inference, proof checking,
> and all the rest.
>
> Look, if you want a logical language, go for it.  Frankly, I am in the
> throes of Language Puppy Love(tm) with Maude right this second (those
> who are interested, check out http://maude.csl.sri.com).  Neat stuff.
> But that doesn't mean I want to twist Haskell to fit that frame.  Nor
> does it mean that I want to abandon Haskell and do all my graphics
> interface programming and scripting via term rewriting logic.  Have no
> fear, Haskell, you are still my first love!

David: BTW, I felt the same way about Maude when I first saw it, but I feel
Maude is less a programming language than it is an algebraic theorem
prover---its programs are not necessarily confluent.

> Sergey Mechveliani wrote:
>
> Adding *rules* to language would NOT cause scripting graphics via term
> rewriting logic. I suppose, you know this.
> If you do not set {rules..} in your program, you would never notice
> they exist.

Huh? Scripting graphics?

> Sergey Mechveliani wrote:
>
> On the second,
> Haskell is related to lambda calculus, to Haskell B. Curry.
> And very probably, it is he, who introduced the rewrite rule technique
> - rules for S,K combinators, and others.
> Let somebody correct me, if i mistake.
> Rather the "graphic interface" affairs, "file handlers", and such,
> can be considered as twisting Haskell to what it should not be.
>
> [more reasons to do algebraic rewriting at compile-time]
...
> Jerzy Karczmarczuk <[EMAIL PROTECTED]>  writes
>
> > Sergey Mechveliani:
>
> >> i asked the list, why the examples deal only with transformations like
> >> (map f).(map g) -> map (f.g),
> >> why not deal with algebraic simplification, say,
> >>(x^2+x+1)*(x-1) -> x^3-1.
>
> > I am afraid that Sergey is dreaming of transforming Haskell into a
> > universal Computer Algebra system. We know for more than 30 years that
> > the general problem of algebraic simplification is a mess.

I think it is best to sidestep the discussion on "what Haskell is for" and
"what Haskell is NOT for."  Face itwe are never going to reach consensus
on such a topic, and I think Sergey's use of the language is certainly as
valid as anyone else's.

I think what is going on is that we all got so excited about Simon's little
language extension that we are already thinking about how it will affect the
way we write programs in the future. It is clearly a very powerful and
desirable extension, at least for a certain class of users.

BUT, at this stage it's just a hack! The semantics are not clear at all and
we don't have any experience with it (at least, not under Haskell). Simon
himself admitted that the matcher is unsatisfactory. Probably one wants a
second-order algorithm here anyway. The interaction with laziness is tricky,
and it can easily destroy the semantics of an unsuspecting user's program.
As it stands, the rules extension does not sit well with Haskell's other
features. (Compare this with Maude, where analogous mechanisms are
intimately related to the foundations of the language.) Mark's comments on
the subject indicate that there are better ways to treat compile-time rules.

I guess what I'm saying is that we should treat the rules feature carefully,
and as a very specialized tool until it is better investigated. Certainly it
is too early to start proposing other features or libraries that build on
it.

--FC






RE: printout database

1999-05-07 Thread Frank A. Christoph

I wrote up some code for you although, judging from the style of your code,
it won't be much help since it uses some language features (higher-order
functions and one abstract type) that your text probably hasn't covered yet.
Frankly, it is a pain to write this stuff in explicit recursive style,
although it probably makes for a good exercise. Sorry.

> My problems are :
> 1. type Person = String
>type Book = String
>type Database = [(Person,Book)]
>exampleBase
>= [("Alice", "Postmn Pat"),("Anna","All Alone"),("Alice","Spot")]
>
>books  :: Database -> Person -> [Book]
>borrowers  :: Database -> Book -> [Person]
>borrowed   :: Database -> Book -> [Bool]
>numBorrowed:: Database -> Person -> Int
>
>   books :: Database -> Person -> [Book]
>   books [] borrowers = []
>   books ((pers,bk):rest) borrowers
> |  pers == borrowers = bk : books rest borrower
> |  otherwise   =  books rest borrower
>
>   {-output :
> books exampleBase "Alice" = ["Postman Pat","Spot"]
>   -}
>
>   borrowers :: Database -> Book -> [Person]
>   borrowers [] books  = []
>   borrowers ((pers,bk):rest) books
> | bk == books = pers : borrowers rest books
> | otherwise   =borrowers rest books
>
>   {- output:
>books exampleBase "Spot" = ["Alice"]
>   -}
>
>   How should I do to  make borrowed and numBorrowed, because it's use
>   String and integer, and i confuse.

  borrowed db bk = map ((== bk) . snd) db

  numBorrowed db pers = length (filter ((== pers) . fst) db)

The map function takes a function f and a list xs and returns the result of
applying f to each member of the list. (.) is function composition. snd
(x,y) = y. (== bk) is a function that returns True if the argument equals
bk, False otherwise. What borrowed does is look at the second component of
each pair in a list, and return a boolean indicating whether it equals bk.
Aw hell, I'll just write it out:

  --- this is untested
  borrowed [] = []
  borrowed ((_,b):rest) = b == bk

As for numBurrowed, filter f xs applies f to each member x of the list xs,
and discards x iff f x is false. You can figure out the rest.

> 2. type Name= String
>type Price   = Int
>type BarCode = Int
>
>type Database = [(BarCode,Name,Price)]
>
>codeIndex :: Database
>codeIndex = [(4719, "Fish Fingers",121),
>   (5643,"NAppies",1010),
>   (3814,"Orange Jelly",56)]
>
>type TillType = [BarCode]
>type BillType = [(Name,Price)]
>
>   How should I do to make function ?
>   - makeBill :: TillType -> BillType
>   - formatBill :: BillType -> String
>   - printBill :: TillType -> String
>   How should I defined BarCode to print (Name, Price)?

   till :: TillType
   till = [4719,5643,3814,4719]

An example till, used below.

   makeBill :: TillType -> BillType
   formatBill :: BillType -> String
   printBill :: TillType -> String

   lookupBy :: (a -> Maybe b) -> [a] -> Maybe b
   lookupBy f [] = Nothing
   lookupBy f (x:xs) = case f x of
 Nothing -> lookupBy f xs
 r   -> r

Um, think of this as a slightly fancy way of selecting a list member, and
postponing error recovery.

   makeBill = map mkBill
 where mkBill code =
 case lookupBy (matchingCode code) codeIndex of
   Just item -> item
   Nothing   -> error "unknown code"
   matchingCode code (c,n,p) | c == code = Just (n,p)
 | otherwise = Nothing

I defined makeBill, which operates over an entire list, in terms of the
local function mkBill, which  operates on just one element. mkBill looks for
a matching code, returns the relevant bill type, or  causes a run-time error
if there is no such code entry in codeIndex.

   formatBill = concat . map fBill
 where fBill (name, price) = name ++ " " ++ show price ++ ", "

(++) is list (here [Char] = String) concatenation. concat is like (++), but
it concatenates a list of strings. show is a kind of generic function that
converts values of most types into a string representation. Your text
probably described a more specialized function for converting integers into
strings in an earlier section.

   printBill t = formatBill bill ++ "Total " ++ total bill
 where total = show . sum . map snd
   bill = makeBill t

This calculates the total price, and tacks it onto a bill generated from the
till t using makeBill. total is a function that sums up the second
components of a list of pairs, and converts the result into a string.

{-
Main> printBill till
"Fish Fingers 121, NAppies 1010, Orange Jelly 56, Fish Fingers 121, Total
1308"
-}

This was the result on my example till, using Hugs.

Maybe I misunderstood you, but I got the feeling that you were searching for
a way to actually print the result as a side-effect, like in C. Notice that
there are no side-effects in the above code. The signature of printBill
call

RE: non-linear patterns

1999-05-07 Thread Frank A. Christoph

Christian wrote:
> Frank A. Christoph gave examples for unintended non-linear patterns,
> among them:
>
> > Or, even more more common:
> >
> >   f (x@(x,y)) = ... --- oops!
>
> If I don't oversee something obvious, this just would fail to
> type-check, so this shouldn't be a problem.

As you can plainly see, in anticipation of such a clever remark I had
already annotated the clause with a comment indicating my reaction. :)

Yeah, that's the ticket...

OK, here's a less likely variant:

  f (y@(x:y)) = ...  --- oops! (just in case :)

whose translation

  f (z@(u:v)) | z == v = ...

is well-typed.

--FC






RE: non-linear patterns

1999-05-06 Thread Frank A. Christoph

In addition to the other arguments mentioned, there is the practical concern
that it becomes quite easy to introduce non-termination by a simple typo:

  f [1...] [2..] where f x x = x  --- oops!

versus, say, the intended

  f [1..] [2..] where f x y = x  .

Or, even more more common:

  f (x@(x,y)) = ... --- oops!

It would be a tad more acceptable, IMO, if one could at least require that
the strictness and equality constraints were expressed explicitly in a
signature, similar to the situation for polymorphic recursion, say like this
(I hope this was the correct usage of Eval; I never really used it much...):

  f :: (Eval a, Eq a) => a -> a -> a
  f x x = x

Anyway, I agree with Brian, who said that this is such a limited class of
constraints that it is not really worth going the extra mile...

--FC

> A friend and I recently discussed why patterns in Haskell are
> restricted to be linear. He found it unintuitive due to his background
> in term rewriting and logic. And he noted that it is easy to compile
> away as in:
...
> My main argument against it was a language design issue, namely that
> suddenly x is required to have an Eq type which cannot be explained by
> looking at its uses in e.
>
> Another problem is that comparing x with x' makes this kind of pattern
> matching super-strict (since x may be reduced to normal form).
>
> Can someone enlighten me on other arguments for or against non-linear
> patterns?






RE: STL Like Library For Haskell

1999-04-30 Thread Frank A. Christoph

> But how important is having a fold well defined.  For many common
> numerical operations such as summing a list, taking the product of a
> list, etc. The order in which the elements get folded does not matter.
> All that matters is that each element gets represented exactly once.

>From an algebraic viewpoint, at least, it's very important, since fold is
_the_  operation over algebraic types and, computational concerns aside,
anything else which respects the abstraction can be defined in terms of it.
For example, in the programming language Charity fold is the only operation
on algebras. (There's a case operator too, but it's just a non-recursive
instance of fold.)

--FC






RE: Monad question

1999-04-22 Thread Frank A. Christoph

filter returns a list, but the rhs of >>= expects an IO. Try:

getDirectoryContents "." >>= return . filter (\s -> head s /= '.')

> I'm working on a little toy program in hbc (now that I have a haskell
> compiler running I decided to give it a try ;), but I seem to 
> have run into
> a monad problem. Here's the snippet in particular (and the results from
> evaluation in hbi):
> > getDirectoryContents "." >>= filter (\(x:_) -> x /= '.');
> [65] Cannot unify types:
> Prelude.IO
> and (Prelude.[])
>  in  (>>=) (getDirectoryContents ".") (filter (\I -> 
> case I of {
>   Prelude.[] -> Pfail "No match in Pinteractive"
> | (:) x I4625 -> (/=) x '.'
> }
> ))
> 
> (The idea here is to filter out all the dot files from the directory
> listing)
> Unfortunately I can't make hide or hair of this. Is this because the
> function being used with filter would break when given an empty 
> list (or is
> that Pfail bit there to handle that breaking?)
> TIA
> -- 
> -Simon Raahauge DeSantis
> 





RE: Dynamic binding and heterogeneous lists

1999-04-21 Thread Frank A. Christoph

> Lennart Augustsson wrote:
> >
> > Kevin Atkinson wrote:
> >
> > > I am sorry for the naive question but how do you fell about adding
> > > dynamic binding to Haskell to make it possible to have heterogeneous
> > > lists with out having to use a nasty union type which has a number of
> > > problems.
> > >
> >
> > What you want(?) is existential types.  Most implementations support
> > this.
>
> Maybe?  What exactly are they.  I have not been able to find a good
> guide which explains the forall and exists qualifier concepts.

There is a short explanation and an example or two in the GHC manual
(section 5.7).

> What I want to be able to do is store a bunch of objects with a common
> base class in a list.  And I also want to be able to add types to this
> heritage without having to modify a single line of the existing code.

The first is trivially possible; with existential types you can put any
object of whatever type into a list with other objects. It's not clear to me
exactly what you mean by the second. Existential types let you hide the
actual type (the witness) of an object, but they do not a priori relate to
OO or inheritance.

That said, you can, however, link the use of existential types to the
Haskell type class system by putting a context in the data declaration (at
least in GHC, and, I think HBC also):

  class State a where
method :: a -> Int

  data Obj = forall a. (State a) => Obj a

Note that the type variable a does not appear as a parameter of the data
declaration.

Then you can construct a heterogeneous list, all of whose "members" have
types that are instances of State (so suppose Int, String and Char are
instances of State):

  xs = [Obj 1, Obj "foo", Obj 'c']

Then you can write a function:

  process :: [Obj] -> Int
  process [] = 0
  process (x:xs) = method x + process xs

This is explained in slightly more detail in the GHC manual. There are also
papers about implementing existential types in functional languages (e.g.,
Laufer & Odersky), and these usually include motivating examples, and papers
about using existential types to represent OO-style objects (e.g., Pierce &
Turner). Mail me if you want a full reference.

--FC





Re: Plea for Change #2: Tools

1999-03-30 Thread Frank A. Christoph

> > I have nothing against someone promulgating a standard CLI for Haskell compilers, 
>but it should not be in the language definition because it is an operating system 
>issue, not a language issue. There are many different ways to present an interface to 
>programs and data, etc., and CLI is only one of them. No need to mandate one 
>particular case in the language definition.
> > Besides, it is difficult to take into account the flexibility that an implementor 
>might need or want. I'm not just talking about flags and options. You said yourself 
>that this sort of thing doesn't apply to an interpreter, for instance, but an 
>interpreter is certainly a valid implementation of the Haskell definition.
> > Finally, I expect that anyone who has sufficient motivation to create a standalone 
>executable, rather than simply using an interpreter like Hugs, will be familiar to 
>some extent with the compiler CLI we have all inherited from cc.
> 
> I strongly disagree with this. 
> All Java compilers know how to do "import chasing".
> When a java source file imports a class, the compiler
> searches the classpath for bytecode.  If it doesn't find bytecode,
> it searches the srcpath for soure code, and compiles this source into 
> valid bytecode, prior to compiling the importing class.
> Java programmers almost never have to use make.

I might remind you that Sun is marketing Java not just as a programming language any 
longer, but in fact as a "platform"---in other words, an operating system in itself. 
Not that I have anything against Java's way of doing this; on the contrary, I think 
it's very convenient. I just don't think it belongs in the language definition.

GHC can do automatic recompilation for you. Do you think this belongs in the standard 
report too? Java does. Eiffel does.

How about HUGS' REPL? It's pretty stable and everyone would benefit from knowing that 
all future interpreters will share the same interface.  Should we standardize that? 
LISP does. Scheme does.

How about GHC's interface file format? Should we standardize that? I don't think so. 
(On the other hand, I do believe very strongly that Haskell needs support for module 
signatures.)

Do I have something against automatic recompilation, REPLs and interfaces files? No. 
Do these belong in the language definition? No. Why not? Because they're not 
language-level issues, not for Haskell.

> Hugs currently has a notion of search path that encompasses this concept,
> but, because Haskell still lacks a sane module namespace*, managing
> these directories is still a pain.

Fine; then GHC can implement import chasing too. No need to put it in the Report, 
though. If it's such a great thing, then every other Haskell implementation will soon 
follow anyway. If you want to standardize it, then put it somewhere else, the Haskell 
Implementation Report or something. I think such a thing could be very useful, 
frankly. It would be a good place to put the new FFI, and the COM/CORBA-Haskell 
mappings too. (BTW, another Good Thing would be to standardize the Haskell abstract 
syntax as a Haskell type, but this properly belongs in the Library Report, I guess.)

But even then, I have to admit that the notion of equating a module with a file makes 
me uneasy. At least, the notion of _mandating_ such an identity does. The whole point 
of Haskell is to abstract _away_ from the underlying machine/platform (not subsume it, 
like Java); this seems like a step backward.

--FC







Re: Plea for Change #2: Tools

1999-03-30 Thread Frank A. Christoph

> I have another pet peeve: ease of use of tools.
> 
> The Haskell standard (intentionally?) leaves the interface to tools an 
> implementors question.  Unfortunate, IMHO, every Haskell compiler I've 
> tried (GHC, NHC, HBC) have just had plain horrible interfaces.
> Interpreters are inherently a different story, but Hugs at least is a
> lot more friendly.

Intentionally, I think.

> I'm not targeting `ghc' in particular, but I do feel that for a
> programming language that stresses cleaness, the tools should reflect
> the same: simple things should be simple to do.
> 
> The report should state the least common denominator interface to
> command line tools, at least up to relatively simple tasks like
> compiling a multi-module program (spanning several directories).
> 
> How about `haskell2 [-I ] '?

I have nothing against someone promulgating a standard CLI for Haskell compilers, but 
it should not be in the language definition because it is an operating system issue, 
not a language issue. There are many different ways to present an interface to 
programs and data, etc., and CLI is only one of them. No need to mandate one 
particular case in the language definition.

Besides, it is difficult to take into account the flexibility that an implementor 
might need or want. I'm not just talking about flags and options. You said yourself 
that this sort of thing doesn't apply to an interpreter, for instance, but an 
interpreter is certainly a valid implementation of the Haskell definition.

Finally, I expect that anyone who has sufficient motivation to create a standalone 
executable, rather than simply using an interpreter like Hugs, will be familiar to 
some extent with the compiler CLI we have all inherited from cc.

--FC







Re: Variables ?

1999-03-17 Thread Frank A. Christoph

>I am relatively new to Haskell, and I'm using Hugs 1.4.
>
>My my source of programming is Java, with the odd bit of basic thrown in for
>good measure.
>
>Now one of the first things I notice about Haskell is that there don't seem
>to be variables in the same sense that there are in other programming
>languages.

Yes, in the sense that you can't update Haskell variables.

>I want to be able to store a value, or a set of values for use
>through-out various functions.

This is a very general and common issue in functional programming
languages like Haskell. Haskell has a general solution based on
monads, but that is definitely the wrong place to start for a
beginner.

The most obvious and fundamental solution is simply to add new
parameters to a function that needs access to "global variables,"
i.e., to thread the values you need through each function call. This
can get annoying in some circumstances, but it has the huge advantage
that each part of your program has an explicit description of its
dependencies---no hidden parameters.

A related solution is to do the above, and then use the curried form
of the function. For example, say x is a global you've threaded
through f and g. Then in g, you partially apply f to x, and just use
that normally:

  f x a b = ...

  g x a b c d = ... h a b ... h c d ... where h = f x

Another solution, when your program deals with lists, is to phrase
your program as a fold. The prelude function foldr has signature:

  foldr :: (a -> b -> b) -> b -> [a] -> b

It takes three arguments: a function f :: a -> b -> b, a value z :: b,
and a list xs :: [a]. One way of describing its effect is to say that
it replaces each cons node in a list with the function f, and the nil
node with z. So:

  foldr f z [a,b,...]
  = foldr f z (a : (b : ( ... : [])))
  = a `f` (b `f` ( ... `f` z))

Some common examples of functions that can be profitably expressed as
folds are:

  sum :: [Int] -> Int
  sum xs = foldr (+) 0 xs  -- add up all the members of a list

  id :: [a] -> [a]
  id xs = foldr (:) [] xs  -- the identity on lists

  map :: (a -> b) -> [a] -> [b]
  map f xs = foldr (\y ys -> f y : ys) [] xs  -- a familiar list function

(BTW, it is common in Haskell to factor out the argument xs which
appears on both sides of these equations. So one would write:

  sum = foldr (+) 0

)

Another way of looking at foldr is as follows. The argument f :: a ->
b -> b takes a value x :: a and a state s :: b, and uses x as input to
calculate a new state s' :: b. Then the argument z :: b of foldr can
be interpreted as an initial state which is successively transformed
using each member of the list as input. For example, in the function
sum above, the state is the running total of the list members (i.e.,
the sum of each suffix of the list).

foldr is polymorphic in the type b of the state, so you can use any
type you want here. You could use a product to store several values
here, or even a record type. So you can think of it as a global store
which exists for the duration of the fold computation only.

BTW, there is also a function foldl which uses the members of a list
in the opposite direction from foldr. There are many other useful
functions dealing with lists in the Prelude. Often, by using these in
combination, you can restate your program in a way that does not
explicitly deal with the issue of global state.

Most datatypes support a fold-like function, so even if you're not
dealing with lists, you can usually easily define the requisite
fold. For example, try defining a fold over binary trees.

--FC






Re: GHC in Japanese Fifth Generation Project!

1999-03-04 Thread Frank A. Christoph

>I was amused to disover recently (thanks to Zhou-san, at POPL) that
>the name GHC (well, really FGHC or `flat' GHC) has already been used,
>by the Japanese Fifth Generation Project.
>
>FGHC stands for Flat Guided Horn Clause, and it's a language that was
>used by the project for knowledge representation:

That would explain something mildly suprising that I saw yesterday on Gerard Huet's 
home page. It includes a list of "major software projects" that he has participated 
in, and near the end is an entry entitled "GHC Interpreter"...!

--FC






Re: syntactic sugar for "arrows"

1999-01-29 Thread Frank A. Christoph

>Ross Paterson wrote:
>> 
>> John Hughes has defined a new abstract view of computation, in his
>> (currently draft) paper "Generalising Monads to Arrows", at
>> 
>> http://www.cs.chalmers.se/~rjmh/Papers/arrows.ps
>
>Has anyone else read this paper? I'm interested in hearing comments, if
>only to point out some things that I may have missed. I'll admit, I
>haven't read the entire paper. I gave up after the 16th page, because it
>was so conceptually unwieldy. It's not that I had difficulty
>understanding how the system works, it's just that I found it difficult
>to believe that such a complex system would be useful in general
>practice.

I've only skimmed it, but it sure looks useful to me. (Thanks for
making us aware of it, Ross.) I've been wondering for a long time
about how to make the LL parsers fit into the monadic framework, and
now we have not only a way to do that, but a more general method for
making parts of any suitable monadic library static.

I think once we see some more examples using Ross's notation rather
than John's point-free one, the uses of the technique will become more
obvious. The thing to remember is that you can write your library and
application using monads first, then, once you're sure the semantics
are right, you can go back and optimize it with arrows by stratifying
the computation.

Even better, you could write your library in monadic form, but write
the application using arrows. You can use the coercions in the paper
to transform your monad into an arrow type (Kleisli arrows), and if
you use Ross's notation in your application, you could more or less
get away with thinking of it as just the usual monadic stuff. That way
you can go back and optimize the library without needing to change the
application. (Of course, you need to make sure that the application
doesn't use all the inherent power of the monad.)

>(Also, I'm not a mathematician who does a significant amount
>of work in category theory, so that may contribute to its apparent
>awkwardness to me.

--FC





RE: Partial Type Declarations

1999-01-15 Thread Frank A. Christoph

Koen Claessen wrote:
> We should allow "partial type specification". The programmer
> is allowed to specify as much information about the type as
> (s)he wants.
>
> The partial type specification would be taken as a "skeleton",
> merely filled in by the type inference algorithm.
>
> Here is how we could specify partial type information
> about foo:
>
>   foo :: (..) => a -> b -> c
>
> Or even:
>
>   foo :: (Giggle a, ..) => a -> b -> c
>   foo :: (Giggle a, Goggle b, ..) => a -> b -> c
>
> (
> Or we could maybe even use (..) at the *type* level:
>
>   foo :: (..) => a -> (..) -> (..)
>   foo :: (..) => (..)
> )
>
> So, we are allowed to use (..) at any place in the
> context (or maybe even type), to show the compiler
> that you know "something" should be there.

I could see what your post was leading up to before I reached the bit above,
and I like the idea, but I was surprised about the syntax. I was expecting
something like this:

  foo :: (?c1, ?c2) => a -> b -> c
  bar :: (Bar a) => a -> ?t -> ?t -> ?s

The advantage of this syntax is that you can indicate that two parts of a
type should be identical. Think of it as "metaquantification," and the
binder is invisible, like in Haskell's usual syntax for type variables.

--FAC




RE:

1999-01-11 Thread Frank A. Christoph

>Assuming you mean "infix to Reverse Polish", I guess you need something that 
>will parse mathematical expressions.  You might like to check out Happy... 
>it's a parser generator for Haskell, and you could write your own infix to RPN 
>program using it.  Alternatively, there is a parsing combinator library that's 
>probably a lot easier to work with, but less general.

No way.  Parser combinators are considerably more general than YACC-style tools.  With 
parser combinators you can easily construct parsers for context-sensitive languages 
and beyond, but Happy is limited to generating parsers for simple context-free 
languages (modulo precedences).

--FC




RE: why I hate n+k

1998-12-01 Thread Frank A. Christoph

Craig Dickson wrote:
>Johannes Waldmann wrote:
>
>>i'd like to support Ralf's opinion: n+k patterns have advantages
>>(when used in a certain manner) so it would be good to keep them.
>>
>>personal reason: right now i'm busy giving tutorials on recursive functions
>>and it's really nice if you can write f(...,y+1) = ... (... y)
>>instead of f(...,y) = ... (... y-1)
>
>Why do you find this makes a significant difference? Personally, I find
>
>f x = ... f (x - 1)
>
>much more intuitive than
>
>   f (x + 1) = ... f x
>
>I see no advantage in the n+k version.

Well, I find the n+k version more intuitive, but I hate n+k patterns.  Haskell goes to 
so much trouble to distinguish type variables from type constructors, and pattern 
variables from data constructors, and infix operators from prefix operators, and then 
it does a 360 by insisting that "+" is going to act as a constructor in this very 
special case.

Actually, I'm a little surprised that people tout this construction as a teaching aid. 
 Yes, it makes the important connection between functions defined over numbers and 
functions defined over algebraic datatypes.  But at the same time it blurs the equally 
important (in Haskell, at least) distinction between data constructors and functions 
over datatypes.  Don't you find that people exposed to this programming style end up 
writing things like

  sort (xs ++ ys) = sort xs ++ sort ys
  ...

?

--FC






RE: Haskel Type Question

1998-11-09 Thread Frank A. Christoph

>I have two functions
>
>> fos:: Num a -> [a] -> [a]
>> fos a x = fos' a 0 x
>
>> fos':: Num a -> a -> [a] -> [a]
>> fos' _ _  [] = []
>> fos' a y1 (x:xs) = y : fos' a y xs
>>where y = a * y1 + x

First of all, I think your type signatures are wrong, unless you've defined your own 
type constructor Num elsewhere.  fos should have a signature like:

fos :: (Num a) => a -> [a] -> [a]

The Num from the prelude is a class, not a type: the context (the part before =>) says 
that the type "a" is an instance of Num.

>Why does
>
>> fos -0.5 [ 1, 1, 1, 1 ]
>
>give me
>
>[a] -> b -> [b] -> [b] is not an instance of class "Fractional"
>
>while
>
>> fos (-0.5) [ 1, 1, 1, 1 ]
>
>evaluates just fine?  I'm using Hugs 1.4.  Thanks.

Without the parentheses, -0.5 is recognized as two lexemes, - and 0.5, with types:

(-) :: (Num a) => a -> a -> a
0.5 :: (Fractional a) => a

Note that, because of the funny precedence rules associated with -, its type here is 
that of a binary function.  I'm not sure why you get exactly the above type error, but 
it's related to this fact.

--FC






RE: composed contexts

1998-11-06 Thread Frank A. Christoph

>> class (Monad m, Monad (t m)) => MonadT t m where
>>   lift :: m a -> t m a
>> 
>> instance (Monad m, Monad (StateT s m)) => MonadT (StateT s) m where
>>   lift m = \s -> m >>= \x -> return (s,x)
>> 
>> If the definitions from the paper can be turned into valid 
>> Haskell 98 w.l.o.g. now, then I'm happy.
>
>No, neither can, and that's not going to change for
>Haskell 98. There is a raft of generalisations to the class
>system (implemented in Hugs and GHC) but which would require
>a much bigger upheaval to Haskell 98.  They are all going to
>be in Haskell 2 (IMHO).  But for H98, sorry.

Oops.  Sorry, I forgot that the MPC stuff, etc. wasn't going into Haskell 98.  I guess 
with all the crossfire I'm getting confused about H98 and H2.

--FC






RE: MonadZero (concluded?)

1998-11-05 Thread Frank A. Christoph

>> The names `mzero' and `mfail' are horrible.  I like Ralph's suggestion
>> to change `fail' to `raise' in the IO monad, and use `fail' for
>> `mfail'.  If that doesn't work, try something else, but please
>> pick names that have a simple meaning in English (as with `return')
>> not monsters like `mzero' and `mfail'.  -- P
>
>I don't like grabbing too many very generic names like zero, plus, fail
>from the user (this is all in the Prelude, remember).  I don't want
>to grab 'raise' because we're going to want it for exceptions in Haskell
>2.  I havn't been able to think of anything better than these monsters.

"throw" is another possibility.  Of course, someone might want to use this identifier 
in a continuation monad.

--FC







RE: composed contexts

1998-11-05 Thread Frank A. Christoph

Simon Peyton-Jones <[EMAIL PROTECTED]>  writes
>
>> - The simple-context restriction.  
>> ...
>> My default position is not to change.  Question: who, apart from
>> Ralf, has actually tripped over the lack of contexts of the
>> form (C (a t1 .. tn)) in Haskell 1.4?  Is their lack a real
>> problem in practice?

Are you talking about contexts in general, or only contexts in function signatures?

For me, the most powerful argument in favor of generalizing contexts is the 
possibility of defining monad transformers, as described in "Monad Transformers and 
Modular Interpreters" by Liang, Hudak and Jones. (Because I love this paper so much. 
:)  I think I convinced you of this once before, when MPC support was being added to 
GHC. One has applications in class declarations, and non-variable arguments in 
instance declarations:

class (Monad m, Monad (t m)) => MonadT t m where
  lift :: m a -> t m a

instance (Monad m, Monad (StateT s m)) => MonadT (StateT s) m where
  lift m = \s -> m >>= \x -> return (s,x)

If the definitions from the paper can be turned into valid Haskell 98 w.l.o.g. now, 
then I'm happy.

--FC






RE: ad hoc polymorphism

1998-11-05 Thread Frank A. Christoph

>Perhaps a "better" solution than ad hoc polymorphism would be to provide
>a more convenient namespace syntax. Am I mistaken in thinking that
>overloading, for overloading's sake, isn't what is wanted; what is
>wanted is to be able to easily differentiate between two functions that
>happen to be named the same? Ad hoc polymorphism is probably the most
>"convenient" differentiation mechanism, but is it the "best"?

Personally, I don't think ad hoc polymorphism outside of the class system sits well 
with Haskell, or the "spirit" of Haskell.

In this particular example, I think Michael's analysis is correct---one only wants to 
differentiate between the prelude "product" and the product defined in some module.  
If you agree to use the identifiers defined in that module only in a qualified way, 
then the only difficulty is in differentiating between the two products _within_ that 
module.  And that can be done by either hiding the prelude version, or changing the 
identifier to, say, "myProduct", and introducing a mechanism for renaming on export.

Using this example as an argument for ad hoc polymorphism is like using a breach of 
table manners at a summit meeting as an excuse for all-out nuclear attack.

--FC




RE: Simon's H98 Notes

1998-10-23 Thread Frank A. Christoph

>Frank A. Christoph wrote:
>> 
>> >Standard ML does not allow this. One important aspect of the SML module
>> >system actually is its strong separation from the core language.
>> 
>> Not that old saw again...!  Ocaml separates the two as well.
>
>Well, the new let-module feature undermines the separation quite a bit,
>because any expression can now contain arbitrary module code -- the
>module system no longer rests on top of the core language.

Syntactically, that's clearly true.  I was under the impression, though, that it was 
_all_ syntax, but it seems I seriously underestimated the magnitude of this extension.

The fact that local modules only warranted a single paragraph in the language manual 
undoubtedly contributed to my misunderstanding...!

Thanks for clearing that up.

--FC






RE: Simon's H98 Notes

1998-10-22 Thread Frank A. Christoph

>> Local imports might be useful, though.  Objective Caml 2.00 has finally
>> caved in and followed Standard ML in allowing expression-local modules.
>
>Standard ML does not allow this. One important aspect of the SML module
>system actually is its strong separation from the core language.

Not that old saw again...!  Ocaml separates the two as well.

You're right, though.  I meant expression-local imports, like

  local open M
  in ...

What Ocaml allows now is things like

  let f x y =
let module M = struct ... y ... end
in ... M.y ...

No first-class doohickeys allowed, so it's really not that far from SML.  I imagine 
that it could be translated into SML along these lines (excuse my rusty SML):

  structure M = struct ... val y = ref  ... end;
  structure X =
struct
  fun f(x,y) = M.y := y; ... !M.y ...
end;

Or maybe not.  I'm not sure of the extent of the feature, but I get the impression 
that it was a small change, mostly for programming convenience.

(In case anyone's interested.)

--FC






RE: Simon's H98 Notes

1998-10-21 Thread Frank A. Christoph

>> Let me get this straight: you want to replace "import qualified"
>> with "with", "import" with "use", and "=" with "rename"?  That
>> sounds like it's 180 degrees away from what I propose.  My intention
>> was to eliminate the need for either new keywords or special
>> syntactic categories for "qualified" and "hiding".  To me it sounds
>> like you just want to rename the identifiers.
>
>what i like about the Ada approach is that it separates
>the two concepts (import of modules, qualification of names).
>i think it's good software engineering to require
>that imports be stated at the top of a module.
>but it's bad to clutter up the namespace at the same time
>(by an unqualified import). that's why i want local "use" clauses as well.
>i have no fear of new keywords, provided they name 
>sensible (and orthogonal) concepts.

No more orthogonal than Haskell's present approach, unless I missed something in your 
explanation.  And as far as syntax goes, Haskell's seems more orthogonal, since there 
is one keyword for the concept of importing, and one "keyword" (special id, 
whatever...) for the concept of qualification, whereas the Ada syntax conflates the 
two.

Local imports might be useful, though.  Objective Caml 2.00 has finally caved in and 
followed Standard ML in allowing expression-local modules.

--FC




RE: Qualified Names

1998-10-20 Thread Frank A. Christoph

>I find it unnatural (and irritating) that:
>  [False ..]==> [False, True]
>  [false..] where false = False ==> [False, True]
>  (Just . Just) 1   ==> Just (Just 1)
>  (just.just) 1 where just = Just   ==> Just (Just 1)
>but   [False..]
>and   (Just.Just)  are illegal.
...
>What would be the consequences of:
>  1. Disallowing '@' as the leading character of a varsym
>  2. Using '@' to form qualified names (since '@' is already a reservedop,
> and a "Module@" prefix could never be confused with "aspatname@")

A less obtrusive option is single quote '.  The unpleasant cases are things like:

  Mod'f'c'

which is not so common, and single character module names:

  'c'M.f

which are pretty uncommon.

--FC






RE: Simon's H98 Notes

1998-10-20 Thread Frank A. Christoph

Johannes Waldmann wrote:
>Frank Christoph writes:
>
>> The convention should be reversed: by default, a module import is qualified.
>> That eliminates the need for both "qualified" and "hiding".  You can rename
>> your identifiers explicitly, as God intended.
>
>are we talking Haskell98 here? anyway, i'd like to second that proposal.

In the best of all possible worlds.  Realistically there's no hope, I imagine, since 
there are few other imaginable syntactic changes which could possibly break so many 
programs.  :)

>even more, i'd like to see Ada naming convetions applied:
>
>you can "with" a package (import a module) (you get qualified visibility)
>you can "use" a previously withe-ed package (unqualified visibility)
>and you can "rename" identifiers. (that would probably be the same
>as "=" for Haskell since we already got referential transparency).
>"with" clauses _must_ be in the header,
>but "use" clauses may also be written for local blocks
>(an additional plus, IMHO)

Let me get this straight: you want to replace "import qualified" with "with", "import" 
with "use", and "=" with "rename"?  That sounds like it's 180 degrees away from what I 
propose.  My intention was to eliminate the need for either new keywords or special 
syntactic categories for "qualified" and "hiding".  To me it sounds like you just want 
to rename the identifiers.

Kris Aerts wrote:
>I'd like to support this proposal. The 'with' and 'use' perfectly explain
>the intention of the import, and in my humble opinion to non-native 
>English speakers even better than qualified vs non-qualified.

FWIW, I find it much harder to distinguish "with" and "use" than "import" and "import 
qualified".  Frankly, I have the same problem with "load" and "use" in ML systems.  It 
must be an acquired taste, like OSes and filepath syntax...

--FC






RE: Felleisen on Standard Haskell

1998-08-04 Thread Frank A. Christoph

>That's just what I intend to do.  I don't see Std Haskell as a big
>deal, but even little deals are worth completing rather than
>leaving as loose ends... and I'm more optimistic than Paul about
>the usefulness of Std Haskell.  I would be happy to find a name
>that was less grand and final-sounding than 'Standard Haskell' though;
>but more final sounding than 'Haskell 1.5'.

That sounds like a good idea.  But why don't we just be honest and call it
Haskell--?  (Or maybe "(-1) Haskell"? :) Unfortunately, that's not even a
legal section because of the funny rules for unary minus...)  Hm...
"Pre-Haskell"?

--FC






RE: Felleisen on Standard Haskell

1998-08-04 Thread Frank A. Christoph

>That said, the more I think about it, I don't really believe that
>"Standard Haskell" will accomplish much.  The fact is that everyone
>wants many of the features in Haskell 2, and so even today would prefer
>using an implementation that is probably not fully compliant with
>anything that is "official" at all.

I feel that way, but I think that Richard Bird and other people using
Haskell in teaching may disagree.  (Come to think of it, wouldn't that
category include you too?)

--FC






RE: Standard Haskell: More lexical/syntactic issues (from Alastair Reid)

1998-06-24 Thread Frank A. Christoph

[I'm replying to both Fergus and Alastair in this message.]

>This is a reply to Fergus Henderson's comments on my proposal.
>
>My answer to all his comments is that consistent languages are
>easier to learn than languages littered with exceptions, special cases
>and random default behaviour.

On the one hand, Haskell has so much syntactic sugar that I am skeptical as
to whether it is really possible to eliminate all of these kinds of
problems.  On the other hand, maybe we can keep the syntactical redundancies
while eliminating exceptional behavior.

>> > 1) Fixity declarations usually look like this:
>> >   infixl 6 +, -
>> >but you can omit the precedence digit and write this instead:
>> >   infixl +, -
>> >
>> >[which is bad...]
>>
>> I don't think it's harder.  Even if the number is specified explicitly,
>> I would *still* have to look up the precedence table in the report,
>> or at least grep the source for the standard prelude, because
>> I don't know what the precedence of the other operators is.

I was surprised to learn that this kind of declaration is possible.  It's a
safe bet that most other people would be too.  Standard Haskell is supposed
to be Haskell 1.4, but streamlined.  If you can eliminate a rarely used
feature, I think you should.  If you can reduce the size of the grammar, I
think you should.

BTW, if I had seen this first in somebody else's source code rather than
here on the list, and it compiled, my first impulse would have been that
there must be a bug in the compiler that accepted it.  Then, after a few
seconds, I would maybe calm down, check the report... and send a message to
this list about it.

>> > 3) Empty contexts are not allowed.
>
>> Who would ever write them?
>>
>> Even for programs that generate Haskell code, it's trivial to handle
>> the empty context case differently.
>
>Probably not many people - but it's still a pointless exception
>and you have to remember to handle that empty case differently.

See below.

>> > 3) Contexts come in two flavours:
>> >  f :: Ord a => a -> a -> Bool
>> >and
>> >  f :: (Ord a, Bounded a) => a -> a -> Bool
>> >[and that's bad]
>>
>> I could live with that, but it might break a lot of existing code.

If I understand this correctly, you want to require the parentheses.  I
believe HBC's grammar needs (or needed---maybe it's fixed now) them, and I
remember when I was writing code for HBC that the extra two keystrokes were
not such a great burden.  If you are going to require this, I think you
should definitely allow #2 above also.

>> > 4) Module headers can be omitted.
>> >If the module leaves out the module header, the header
>> >   module Main(main) where
>> >is assumed.
>> >[and that's a mistake]
>>
>> Fix the compilers.  If there's no module header, the compiler should
>> not include the module name (Main) in the error messages.

What do you propose they should use in its stead?  "Type error in the module
formerly known as Main"?  ;)

>That's be nice AS WELL but why not simplify the report by removing
> pointless defaults.
>
>There's an argument going around that it must be possible teach Haskell
>without having to mention the word "module" in the first month.
>This argument is used to justify reexporting all kinds of rubbish
>from the Prelude (and is something I have argued against in the Standard
>Haskell discussion).

Larry Paulson has been lauded for introducing and using modules much earlier
in the second edition of his book "ML for the Working Programmer", and that
book is often used as an introduction to FP by beginners (despite the
title).  I agree that it is "cleaner" from the teacher's standpoint to avoid
mention of modules in the beginning, but so what?

Haskell is supposed to be a language suitable both for education and
programming in the large (PITL).  Fine.  But nobody said it had to be a
scripting language and, although I think functional languages are great for
that purpose, Haskell should not be both a scripting language and a language
for PITL at the same time.

Furthermore: a language suitable for scripting is not necessarily suitable
for education, nor vice versa.  Certainly no one would start off a bunch of
freshmen on Perl!  It seems to me that many of the syntactic oddities above
might be viewed as symptoms of conflating one with the other.  For example,
in a scripting language, it is desirable to have lots of defaults, etc. so
that there is as little time as possible between the time you start to write
a program and the time you get it running.  That's possible because
scripting languages are often targeted at one specific domain, and so you
can choose your defaults accordingly.  But Haskell is supposed to be a
general-purpose language, so default behavior is not much of a benefit.

If you want a functional scripting language with H-M type inference and type
classes and monads, that's great, but maybe it should be something separate
from Haskell.

--FC






Re: SLPJ Moving to Microsoft

1998-05-22 Thread Frank A. Christoph

>> More specifically, I plan to continue beavering away on GHC.
>> GHC is public domain software, and Microsoft are happy for it to
>> remain so, source code and all.
...
>GHC is a wonderful, inspiring piece of software. It is good to know
>that it will remain in the public domain. I didn't know, however, that
>we should be grateful to Microsoft for that. Am I the only one who
>pretends having misunderstood this? [Here you add some smileys].

I was a little surprised to read this too.  You make it sound as if GHC's
free status was in jeopardy.  Should we all go running for the hills if
Microsoft decides to crook its little finger in our direction?  I'm glad
that you will continue to contribute to GHC, but it scares me to think that
GHC's continued existence depends on Microsoft's "happiness."

Well, I guess having some (more?) `declarative people' at Microsoft is a
step in the right direction.  Congratulations on your new job.

But you know,

  When the [functional] revolution comes [the people at Microsoft] will be
the first with
  their backs against the walls. --- adapted from Douglas Adams

:) [I'm not afraid to add my smileys...]

--FC

P.S.: Why do I lately keep getting this error when I send something to a
Glasgow-sponsored list?

This report relates to your message: Subject: RE: SLPJ Moving to Microsoft,
  Message-ID: <000801bd8558$1a5c1320$[EMAIL PROTECTED]>,
  To: <[EMAIL PROTECTED]>
Your message was not delivered to   [EMAIL PROTECTED]
for the following reason:
Unable to perform the conversion required for delivery
Conversion failure at site 'dcs.gla.ac.uk' for recip
'[EMAIL PROTECTED]' Reason: Can't convert bodypart
'mime-unknown'

* The following information is directed towards the local administrator
* and is not intended for the end user
*
* DR generated by: mta vanuata.dcs.gla.ac.uk
* in /PRMD=UK.AC/ADMD= /C=GB/
* at Fri, 22 May 1998 08:54:52 +0100
*
* Converted to RFC 822 at dcs.gla.ac.uk
* at Fri, 22 May 1998 08:55:06 +0100
*
* Delivery Report Contents:
*
* Subject-Submission-Identifier: [/PRMD=UK.AC/ADMD=
/C=GB/;<000801bd8558$1a5c1320$6f50ebca@]
* Content-Identifier: RE: SLPJ Movi...
* Original-Encoded-Information-Types: ia5-text
* Content-Correlator: Subject: RE: SLPJ Moving to Microsoft,
*   Message-ID:
<000801bd8558$1a5c1320$[EMAIL PROTECTED]>,
*   To: <[EMAIL PROTECTED]>* Recipient-Info:
[EMAIL PROTECTED],
* /S=haskell/OU=dcs/O=glasgow/PRMD=UK.AC/ADMD= /C=GB/;
* FAILURE reason Conversion-Not-Performed (2);
* diagnostic Conversion-Impractical (8);
* supplementary info "Conversion failure at site 'dcs.gla.ac.uk'
* for recip '[EMAIL PROTECTED]' Reason: Can't convert
* bodypart 'mime-unknown'";
** End of administration information








RE: SQL transactions, RPC, and write protected files

1998-05-20 Thread Frank A. Christoph

I suppose it depends on the compiler implementation.  In GHC, you can just
use unsafePerformPrimIO and _ccall_.  There is a section in the manual
called "Avoiding monads" that describes this.

--FC

-Original Message-

>Is there a way to promise Haskell that external calls which return
>data do not change any state so that you can use them within
>functions rather than only within do sequences.  It would make certain
>classes of CGI applications much easier (I really want a Haskell version
>of PHP). Examples:







RE: Pattern Match Success Changes Types

1998-05-12 Thread Frank A. Christoph

>> Actually, GHC does finally discard type information right at the
>> end, so we could do an extra bit of CSE there, but frankly I doubt
>> it would buy very much.  But I'm willing to stand corrected.
>
>I don't think you can say this. Granted in this trivial example
>we are only talking about wasting constructor record per
>'demo expression'. But in other more complex examples we could be
>talking several. Also the total heap space that gets wasted this way
>is not an intrinsic property of the demo function. It depends on
>the number of 'demo expressions' (or similar) which get reduced.
>I don't think you can predict how many this will be with any generality.
>In some programs it could conceivably be huge Nos. Couldn't it?.
>It would be nice to re-use the existing constructors, even if the
>type checker says thats illegal.


I'm experiencing a little bout of deja vu here, so excuse me if it turns out
that I'm repeating myself.  (I could swear I already posted this, but it's
not in my "Messages Sent" folder...)

With regard to merging Either instances, I agree with Simon that for most
programs this will not buy you much, but there are two common kinds of
programs where one could expect a significant effect on performance, just
because of sheer scale.  The first is any program which uses an
error/exception monad on a program-wide scale.  The second is a program that
uses Chalmers' fudgets library since, as I recall, the type Either plays a
prominent role in the "messaging" system.

--FC






RE: Sockets & Green Card

1998-05-06 Thread Frank A. Christoph

>Hope to have a release ready soon. A translator that spits out IDL
>specs given Green Card 2 input will not be supplied, as the two
>approaches to describing bindings to foreign functionality are
>fundamentally different. Green Card 2 starts with a Haskell type
>signature and tries to derive the (proto)type of the external function
>from it, with the programmer making up the difference in C.
>
>The IDL compiler goes the other way, starting with an external
>specification of a function/type. It is mapped to a corresponding
>Haskell function/type, leaving the programmer to make up the
>difference this time in Haskell rather than C.


Just out of curiosity, could you give a simple example of this (an IDL spec
plus the accompanying Haskell code)?

--FC






Characterizations of H-M type inference?

1998-04-24 Thread Frank A. Christoph

Does anyone know if Hindley-Milner type inference has been characterized in
a non-operational way?  I mean either some sort of canonical correspondence
(as the simply typed lambda-calculus with intuitionistic natural deduction)
or some statement that describes it in terms of a universal property, like
in category theory.  For that matter, is there any work at all which has
characterized the notion of type inference (not just H-M) for functional
and/or related languages in a declarative manner, perhaps in terms of proof
theory?

Thanks in advance.

If I receive many substantial private responses, I will post a summary
later.

--FC






Standard Haskell Libraries

1998-04-24 Thread Frank A. Christoph

Suggestion for Standard Haskell:

Copy all the stuff in the Prelude to the standard libraries, at least when
there is an obvious module for them to go to.  For instance, head and tail
should appear in the List module.  I doubt I'm the only one who can't
remember if a particular list function, for example, appears in the Prelude
or the libraries...

I am not suggesting that we should throw out the Prelude (although I think
we should), just that the identifiers should at least _additionally_ appear
in the proper places; it could be done, for example, by just re-exporting
the identifiers in one direction or the other, depending on the dependencies
(cough).

--FC






RE: Operators (was: Standard Haskell)

1998-03-30 Thread Frank A. Christoph

>Alex Ferguson wrote:
>
> | Frank A. Christoph:
> | > I hope that Either will be renamed to (+), or at
> | > least deprecated in favor of (+).
> |
> | I'd basically agree with Frank here, though presumably for consistency
> | with Koen's (very reasonable) proposals, this would need to be the
> | symbol (:+:) -- or characters to that effect -- for consistency.
>
>I agree.
>
>Note that the symbol (+) as a type, would become a type _variable_. I
>think, just as it is usefule to have (+) as a formal parameter of a
>function, it is useful to have operators as type variables also.


Ah yes, I missed that little detail.

I very much like the idea of using (+) as a type variable.  For example, it
could be used as the parameter name of a functor type that plays the role of
coproduct in some category.

--FC






RE: Standard Haskell

1998-03-27 Thread Frank A. Christoph

> * Secondly, "Restrictions on name spaces removed". As an addition to
>this, I would like to propose the following modest extension to Haskell.
>Why don't we allow type constructors with more than one argument to be
>written as operators? An obvious example to define would be:
>
>  data a :+: b = Left a | Right b
>  data a :*: b = Pair a b


Yes to this.  I too have always wondered why this wasn't allowed in the
first place.

>Valid syntax would then also be:
>
>  (>+<) :: F a b -> F c d -> F (a `Either` c) (b `Either` d)


And if the above passes, I hope that Either will be renamed to (+), or at
least deprecated in favor of (+).  (Personally I think that (,) should be
renamed to (*) as well---or vice versa for the corresponding function
value---but I won't push it, since I know that (,) appears in a million
Haskell programs.)  Either is a very useful type, but its name is too long
and I hate it when type signatures span more than one line.

--FC