Re: Unicode (Re: Reverse composition)

1999-10-12 Thread Ralf Muschall

Lennart Augustsson wrote:

 It's not hard to find a text editor, use w.g. wily.  It's widely available.

But it is hard to use some nonstandard (i.e. neither vi nor emacs)
editor just for one special kind of source code - it means to lose
all the keybindings, highlight settings, 100-lines-of-definition-macros
etc. which are usually the result of many years of work and ergonomical
optimization.

In particular, the section "Drawbacks and problems" of 
http://www.cs.su.oz.au/~gary/wily/intro.html
says that wily is not for me :-)

I'd prefer to keep the language itself in ASCII (remember APL died for
doing otherwise) and have it support whatever character sets only as
data.
(One might allow alternative non-ASCII characters for people who have
them,
similar to `ä´ as a special code which behaves (more or less) equivalent
to `\"a´ in LaTeX).

In addition, leaving ASCII would break on DOS and Win3.x - it is not
probable that Bill Gates will go back and create UTF libraries for them.
Other not-very-recent systems might break as well.

Ralf






Unicode (was RE: Reverse composition)

1999-10-11 Thread Tom Pledger

Brian Boutel writes:
  [...]
  
  If the supply of suitable Ascii symbols seems inadequate, remember
  that Haskell uses Unicode. There is no reason to limit symbols to
  those in the Ascii set.

While we're on the subject, I suggest Unicode as a Hugs/GHC wish list
item.  In particular, I'd like to use the familiar symbols for union,
intersection, and subset, without resorting to Ascii art, please.

Regards,
Tom






Reverse Composition and Preprocessor Discussions

1999-10-10 Thread Brian Boutel

On Sunday, 10 October 1999 00:09, Lennart Augustsson [SMTP:[EMAIL PROTECTED]] 
wrote:
 Marcin 'Qrczak' Kowalczyk wrote:
 
  Sat, 9 Oct 1999 12:42:20 +1300, Brian Boutel [EMAIL PROTECTED] pisze:
 
   Be careful. '-' is two symbols. Replacing it by one symbol can change the
   semantics of a program by affecting layout.
 
  No, because only the indent before the first non-whitespace character
  in a line matters. Haskell programs can be typeset even in proportional
  font as long as indents have correct relationships between their
  lengths.
 
 You must be using a different Haskell than I am.  :-)
 Consider these two fragments:
 a = x + y where x = 1
  y = 1
 vs.
 a = x ++ y where x = 1
  y = 1
 
 They have very different syntactical meaning.
 

It occurs to me that this signals a problem with the macro preprocessor proposals. 
Macro expansion can affect relative indentation, and therefore create errors which 
would
be hard to find because the expanded form is not normally visible.

This strongly suggests either
a) Restrict preprocessing to whole-line inclusion/exclusion (conditional compilation), 
including
#define, #ifdef, #elseif, #else, etc, or
b) Allow general macro expansion, but do the "pre-"processing after layout processing. 

--brian









Unicode (Re: Reverse composition)

1999-10-09 Thread Marcin 'Qrczak' Kowalczyk

Sat, 9 Oct 1999 12:42:20 +1300, Brian Boutel [EMAIL PROTECTED] pisze:

 Be careful. '-' is two symbols. Replacing it by one symbol can change the 
 semantics of a program by affecting layout.

No, because only the indent before the first non-whitespace character
in a line matters. Haskell programs can be typeset even in proportional
font as long as indents have correct relationships between their
lengths.

 If the supply of suitable Ascii symbols seems inadequate, remember
 that Haskell uses Unicode. There is no reason to limit symbols to
 those in the Ascii set.

Yes. Unfortunately under Linux (and probably many other systems)
it is not easy to use Unicode yet, because of lack of text editors
and only partial support from the system (e.g. locale is going to
support UTF-8 in the near future, ncurses does not support UTF-8).

But when Unicode finally comes... How should Haskell's textfile IO
work? And FFI? I'm sure most people will want to use not only Unicode
and I'm afraid many people would treat Haskell as broken when it does
not output non-UTF8 8bit characters in source strings without a change.

I think that the minimum, acceptable and on the other hand reasonably
implementable, is the ability to treat source as ISO-8859-1 or UTF-8,
and treat outside world as ISO-8859-1 or UTF-8, in both places as
chosen with some magical switches. ISO-8859-1 would emulate other 8bit
encodings by transparently passing characters 0..255 through IO and
FFI. And future charset conversion functions will probably represent
8bit encodings as Unicode characters 0..255, even though they "really"
are ISO-8859-1.

Haskell standard speaks nothing about UTF-8, but it's about the only
sensible way of exchange between internal Unicode and external 8bit
streams, and AFAIK it will be / is used in many systems as external
representation.

In a few months I will probably want to use Unicode in Haskell and
will have to temporarily use `type UChar = Int'.

-- 
 __("Marcin Kowalczyk * [EMAIL PROTECTED] http://kki.net.pl/qrczak/
 \__/  GCS/M d- s+:-- a22 C++$ UL++$ P+++ L++$ E-
  ^^W++ N+++ o? K? w(---) O? M- V? PS-- PE++ Y? PGP-+ t
QRCZAK  5? X- R tv-- b+++ DI D- G+ e h! r--%++ y-







Re: Unicode (Re: Reverse composition)

1999-10-09 Thread Lennart Augustsson

Marcin 'Qrczak' Kowalczyk wrote:

 Sat, 9 Oct 1999 12:42:20 +1300, Brian Boutel [EMAIL PROTECTED] pisze:

  Be careful. '-' is two symbols. Replacing it by one symbol can change the
  semantics of a program by affecting layout.

 No, because only the indent before the first non-whitespace character
 in a line matters. Haskell programs can be typeset even in proportional
 font as long as indents have correct relationships between their
 lengths.

You must be using a different Haskell than I am.  :-)
Consider these two fragments:
a = x + y where x = 1
 y = 1
vs.
a = x ++ y where x = 1
 y = 1

They have very different syntactical meaning.


  If the supply of suitable Ascii symbols seems inadequate, remember
  that Haskell uses Unicode. There is no reason to limit symbols to
  those in the Ascii set.

 Yes. Unfortunately under Linux (and probably many other systems)
 it is not easy to use Unicode yet, because of lack of text editors
 and only partial support from the system (e.g. locale is going to
 support UTF-8 in the near future, ncurses does not support UTF-8).

It's not hard to find a text editor, use w.g. wily.  It's widely available.
It can be hard to find support for your favourite editor though.


 But when Unicode finally comes... How should Haskell's textfile IO
 work? And FFI? I'm sure most people will want to use not only Unicode
 and I'm afraid many people would treat Haskell as broken when it does
 not output non-UTF8 8bit characters in source strings without a change.

These are good questions, and we need to start using Unicode to iron out any
wrinkles that are left in Haskell.


 Haskell standard speaks nothing about UTF-8, but it's about the only
 sensible way of exchange between internal Unicode and external 8bit
 streams, and AFAIK it will be / is used in many systems as external
 representation.

Well, some Haskell implementations come with UTF-8 conversion functions.


--

-- Lennart








Re: Idiomatic Haskell extension library (Re: Reverse composition)

1999-10-09 Thread William Lee Irwin III

On Sat, Oct 09, 1999 at 04:52:20PM +0100, [EMAIL PROTECTED] wrote:
 I'd include composition, function products (as in Joe English's
 message) and operations on boolean predicates:
 (f  g) x = f x  g x
 (f ||| g) x = f x || g x
 notF f x = not (f x)

One way to get around this would be to make a class Boolean (or, better
yet, Lattice) with not too many constraints and then have something on
the order of

module Lattice where
-- it's important that there isn't an Eq a = Lattice a constraint
-- because functions aren't of observable type; unless you want to
-- define functions as a trivial instance of Eq, like I had to for
-- arithmetic operations
class Lattice a where
(), (|||):: a - a - a

instance Lattice Bool where
()   = ()
(|||)   = (||)

instance Lattice b = Lattice (a-b) where
f  g = \x - (f x)  (g x)
f ||| g = \x - (f x) ||| (g x)

-- the end of the code

and this would allow things like
let f True  = False ;
f False = True ;
g _ = False
in
(f ||| g) False

and

let f True  = False ;
f False = True ;
g _ = False
in
(f  g) True

to be interpreted naturally. There is no class corresponding to  and ||
in the Prelude, which is why I had to do it this way.


Bill






Re: Reverse composition

1999-10-09 Thread Heribert Schuetz

Jonathan King writes:
 How about:
 
 f | g | h | ...
 
 for [reverse composition], and
 
 g | f
 
 for "normal" composition?

I like this because it follows the easy-to-remember rule

  "Use symmetric glyphs for commutative operations and asymmetric glyphs
  for non-commutative operations. Reflect glyphs for flipped operations."

which I would suggest as a general guideline. (Unfortunately I don't
know whom to credit for this rule. Might be someone working on visual
programming.)

I understand the desire for a lightweight glyph for function composition
and also the desire for something similar to the usual mathematical
notation. But in this case I find reflected glyphs for forward and
backward composition far more appealing. (I wouldn't suggest replacing
"-" by an asymmetric glyph though.)

Similarly, I would prefer a pair of reflected symbols for normal and
reversed function application, e.g., $ and $. (Yes, these are not 100%
reflected, but almost.)

Heribert.






Idiomatic Haskell extension library (Re: Reverse composition)

1999-10-09 Thread Jon . Fairbairn

On  9 Oct, Heribert Schuetz wrote:

[(f | g) x = f (g x); (f | g) x = g (f x)]

"Use symmetric glyphs for commutative operations and asymmetric glyphs
for non-commutative operations. Reflect glyphs for flipped operations."

That would make me happy.

  which I would suggest as a general guideline.

and I'd go along with that.

  Similarly, I would prefer a pair of reflected symbols for normal and
  reversed function application, e.g., $ and $. (Yes, these are not 100%
  reflected, but almost.)

and that.  For the record, my taste isn't particularly bothered by
multi-character symbols; what swayed me in the past was the argument
that it was a problem for other folk.


* * *

Anyway -- I'd like to suggest that we put a library containing
definitions of simple operators of general utility somewhere readily
accessible.  The precise choice of name for operator doesn't matter
(though I think a certain amount of discussion is worthwhile).  What
matters is that for common functions such as the ones we have been
discussing the Haskell community should in general use the same names.

I'd include composition, function products (as in Joe English's
message) and operations on boolean predicates:

 (f  g) x = f x  g x
 (f ||| g) x = f x || g x
 notF f x = not (f x)

(I'm not wedded to those names.)

Where do we put it?



-- 
Jón Fairbairn [EMAIL PROTECTED]








Re: Reverse composition

1999-10-08 Thread Kevin Atkinson

On Fri, 8 Oct 1999 [EMAIL PROTECTED] wrote:

 Some time ago there was a discussion about what to call reverse
 composition (I can't find it in the archive - needs a search option?)
 
 Just now I thought of .~ from . for composition and ~ (tilde, but
 commonly called twiddle) for twiddling the order about.
 
 Maybe we could adopt that as normal usage?

Interesting however I like (.| and $|) since it represents a unix pipe.
The ~ tilde is generally used for not.
My guess is that it is not in the standard becuase we can't agree on which
one is best.

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







Reverse composition

1999-10-08 Thread Jon . Fairbairn

Some time ago there was a discussion about what to call reverse
composition (I can't find it in the archive - needs a search option?)

Just now I thought of .~ from . for composition and ~ (tilde, but
commonly called twiddle) for twiddling the order about.

Maybe we could adopt that as normal usage?
-- 
Jón Fairbairn [EMAIL PROTECTED]










Re: Reverse composition

1999-10-08 Thread Jonathan King


On Fri, 8 Oct 1999, Hamilton Richards Jr. wrote:

 At 1:01 PM -0500 10/8/1999, [EMAIL PROTECTED] wrote:
 
 Some time ago there was a discussion about what to call reverse
 composition (I can't find it in the archive - needs a search option?)
 
 Just now I thought of .~ from . for composition and ~ (tilde, but
 commonly called twiddle) for twiddling the order about.
 
 Maybe we could adopt that as normal usage?
 
 Assuming that "reverse composition" means
 
   f .~ g  =  g . f
 
 I kind of like . ("forward composition"), which I first saw in Simon
 Thompson's book.

Discussion of what glyph(s) to use for the reverse composition operator
just reminded me of the fact that you might really want to think up
a new "forward" composition operator, as well.  Twice in the past few
months I've seen the suggestion that "." really should be used for
what the vast majority of programming languages already use it for,
namely, a part of the record syntax.   If you look at the code 
examples in the "Lightweight extensible records" paper:

   http://research.microsoft.com/Users/simonpj/#records

or those in the O'Haskell work:

   http://www.cs.chalmers.se/~nordland/ohaskell/index.html

I think you might see the point.  (No pun back there, I promise...) I
understand where using "." to mean composition came from, and I know that
it's a long-standing tradition in at least the Haskell community, but I
don't think the visual correspondence of . to the typographic glyph
"raised open circle" is so close that you'd really like to explain why
you diverged from current usage so much as to choose "." to mean
"composition".  Especially since to "reverse" it, you end up using .
 
 It makes pipelines easy to read:
 
   f . g . h . ...

How about:

f | g | h | ...

for the above, and

g | f

for "normal" composition?  (Or does this step on some other notation out
there already?) You save a character, get a nice, reversible glyph, and
get to make a different point somewhere else.

jking







Re: Reverse composition

1999-10-08 Thread Joe English


[EMAIL PROTECTED] wrote:

 Some time ago there was a discussion about what to call reverse
 composition (I can't find it in the archive - needs a search option?)

 Just now I thought of .~ from . for composition and ~ (tilde, but
 commonly called twiddle) for twiddling the order about.

 Maybe we could adopt that as normal usage?


I've also seen  .|  and |.  used for this purpose (by
analogy with Unix pipes.)


John Hughes' Arrow library spells it "", but generalized
to arbitrary arrows.   At the (-) instance it's the same
as "flip (.)".


Along the same lines, are there accepted conventional infix operators
for the functions with types:

(a0 - b0) - (a1 - b1) - (a0,a1) - (b0,b1)
(a  - b0) - (a  - b1) - a - (b0,b1))

(a0 - b0) - (a1 - b1) - Either a0 a1 - Either b0 b1
(a0 - b)  - (a1 - b)  - Either a0 a1 - b

(the last one is called "either" in the standard Prelude).

I personally like:

(f * g) (x,y) = (f x, g y)
(f  g) x = (f x, g x)
(f + g) (Left x)  = Left (f x)
(f + g) (Right y) = Right (g y)
(f | g) (Left x)  = f x
(f | g) (Right y) = g y

Hughes spells these ***, , +++, and ||| (again generalized
to arbitrary arrows), but those don't look as nice typeset IMHO.

I also like:

apfst :: (a - c) - (a,b) - (c,b)
apsnd :: (b - c) - (a,b) - (a,c)
apl   :: (a - c) - Either a b - Either c b
apr   :: (b - c) - Either a b - Either a c

These are called "first", "second", "left", and "right"
in the Arrow library.



--Joe English

  [EMAIL PROTECTED]






Re: [haskell] Reverse composition

1999-10-08 Thread Christopher Jeris

Personal taste in infix operators seems to be another good argument for a
camlp4-style preprocessor for Haskell.  For instance I would like to use
'o' for composition (since anybody who uses 'o' for a variable gets what
they deserve!) but I guess that would make the lexer not so nice.
I would also use : for typing and :: for cons, as in ML.  But everybody
has their own taste in these things and it would be nice if we could all
pick ours.

Chris Jeris







Re: [haskell] Reverse composition

1999-10-08 Thread Jon . Fairbairn

On  8 Oct, Christopher Jeris wrote:
  Personal taste in infix operators seems to be another good argument for a
  camlp4-style preprocessor for Haskell. 

Please no!  I want to be able to read other folks programmes and vice
versa.  The whole point of suggesting a particular glyph on this foram
is so that we can swallow our personal pride and use a common language.

 For instance I would like to use
  'o' for composition (since anybody who uses 'o' for a variable gets what
  they deserve!) but I guess that would make the lexer not so nice.

You could use `o` already.  f `o` g looks no worse to me than f . g
et al.

-- 
Jón Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH  +44 1223 570179 (pm only, please)







Re: Reverse composition

1999-10-08 Thread Marcin 'Qrczak' Kowalczyk

Fri, 8 Oct 1999 19:01:07 +0100 (BST), [EMAIL PROTECTED] 
[EMAIL PROTECTED] pisze:

 Some time ago there was a discussion about what to call reverse
 composition (I can't find it in the archive - needs a search option?)
 
 Just now I thought of .~ from . for composition and ~ (tilde,
 but commonly called twiddle) for twiddling the order about.

What about doing the analogous thing for the reverse application
as well?

They could also be . and $

But probably it is sufficient to use `(.d) (.c) (.b) a' as `a.b.c.d',
and `($obj) method arg1 arg2 arg3' for those wanting OO-like order.

-- 
 __("Marcin Kowalczyk * [EMAIL PROTECTED] http://kki.net.pl/qrczak/
 \__/  GCS/M d- s+:-- a22 C++$ UL++$ P+++ L++$ E-
  ^^W++ N+++ o? K? w(---) O? M- V? PS-- PE++ Y? PGP-+ t
QRCZAK  5? X- R tv-- b+++ DI D- G+ e h! r--%++ y-







Re: Reverse composition

1999-10-08 Thread Jon . Fairbairn

On  8 Oct, Jonathan King wrote:
  I think you might see the point.  (No pun back there, I promise...) I
  understand where using "." to mean composition came from, and I know that
  it's a long-standing tradition in at least the Haskell community, but I
  don't think the visual correspondence of . to the typographic glyph
  "raised open circle" is so close that you'd really like to explain why
  you diverged from current usage so much as to choose "." to mean
  "composition". 

Back in the early Haskell discussions we argued about various options,
but I think Richard Bird and Phil Wadler were insistent that, because
function composition is so important for functional programming, the
symbol used should be something with very low visual weight.  Nowadays
we might actually think of using ° (which would suggest º or § for the
reverse ;-).  Not to mention using · for composition...

Even though I disagreed with the use of . in the original case, I was
persuaded, and still think it ought to be a single
character. Unfortunately most of the other good candidates have been
used elsewhere.

-- 
Jón Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH  +44 1223 570179 (pm only, please)








Re: Reverse composition

1999-10-08 Thread Hamilton Richards Jr.

At 1:01 PM -0500 10/8/1999, [EMAIL PROTECTED] wrote:
Some time ago there was a discussion about what to call reverse
composition (I can't find it in the archive - needs a search option?)

Just now I thought of .~ from . for composition and ~ (tilde, but
commonly called twiddle) for twiddling the order about.

Maybe we could adopt that as normal usage?

Assuming that "reverse composition" means

f .~ g  =  g . f

I kind of like . ("forward composition"), which I first saw in Simon
Thompson's book.

It makes pipelines easy to read:

f . g . h . ...

--Ham



--
Hamilton Richards Jr.Department of Computer Sciences
Senior Lecturer  Mail Code C0500
512-471-9525 The University of Texas at Austin
SHC 434  Austin, Texas 78712-1188
[EMAIL PROTECTED]
--








Re: Reverse composition

1999-10-08 Thread Jon . Fairbairn

On  8 Oct, Joe English wrote:
  [I wrote]:
  Just now I thought of .~ from . for composition and ~ (tilde, but
  commonly called twiddle) for twiddling the order about.

  I've also seen  .|  and |.  used for this purpose (by
  analogy with Unix pipes.)

  John Hughes' Arrow library spells it "",

Oh well, I thought it might be cute enough to solve the argument, but
obviously not...

  Along the same lines, are there accepted conventional infix operators
  for the functions with types:
  
   (a0 - b0) - (a1 - b1) - (a0,a1) - (b0,b1)
   (a  - b0) - (a  - b1) - a - (b0,b1))
  
   (a0 - b0) - (a1 - b1) - Either a0 a1 - Either b0 b1
   (a0 - b)  - (a1 - b)  - Either a0 a1 - b
  
  (the last one is called "either" in the standard Prelude).

These were on my list to think of names as well.  In ponder I had `
(like a raised comma) and  (product of functions).

  I personally like:
  
   (f * g) (x,y) = (f x, g y)
   (f  g) x = (f x, g x)
   (f + g) (Left x)  = Left (f x)
   (f + g) (Right y) = Right (g y)
   (f | g) (Left x)  = f x
   (f | g) (Right y) = g y

I'd go along with those -- if for no other reason than you being first
to suggest them, and wishing for less argument. They look OK too.


-- 
Jón Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH  +44 1223 570179 (pm only, please)