Re: [Haskell-cafe] Re: Haskell code for this example of flow control

2006-02-04 Thread Bulat Ziganshin
Hello MaurĂ­cio,

Friday, February 03, 2006, 7:28:16 PM, you wrote:

MI wonder if I could write a generic while based on your example:

while :: (a - IO a) - (a - Bool) - IO ()

MI'll probably learn something trying that.

i have about 5-10 imperative control structures defined in my
common lib, including while, until, forever, doInChunks


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


[Haskell-cafe] request for help

2006-02-04 Thread Bulat Ziganshin
Hello haskell-cafe,

i'm wrote new general i/o library called Streams. it's so great that i
hope it will eventually replace using Handles. i plan to present it in
Haskell list on Monday. in order to do it i wrote overview of library
facilities. the problem is that i'm not native english speaker and i
feel that my text is awkward, in best case. when i wrote last time
docs about Arrays, Cale Gubbard fixed lots of my misspellings on wiki
page :) this time i try to go different way - i published my version
of report at the http://haskell.org/haskellwiki/Library/Streams page
and ask your help in correcting it. it will allow to include in
presentation the proper English text that is much more pleasing for
readers than my scribbles :)

so, please correct text at this wiki according to English rules. even
if you correct paragraph or two, that will forward the work further

-- 
Best regards,
 Bulat  mailto:[EMAIL PROTECTED]



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


[Haskell-cafe] Re: strict Haskell dialect

2006-02-04 Thread Ben Rudiak-Gould

Chris Kuklewicz wrote:

Weak uses seq to achieve WHNF for it's argument


newtype Weak a = WeakCon {runWeak :: a}
mkWeak x = seq x (WeakCon x)
unsafeMkWeak x = WeakCon x


This doesn't actually do what you think it does. mkWeak and unsafeMkWeak are 
the same function.


mkWeak 123 = seq 123 (WeakCon 123) = WeakCon 123
unsafeMkWeak 123 = WeakCon 123
mkWeak _|_ = seq _|_ (WeakCon _|_) = _|_
unsafeMkWeak _|_ = WeakCon _|_ = _|_

To quote John Meacham:

| A quick note,
| x `seq` x
| is always exactly equivalant to x. the reason being that your seq
| would never be called to force x unless x was needed anyway.
|
| I only mention it because for some reason this realization did not hit
| me for a long time and once it did a zen-like understanding of seq
| (relative to the random placement and guessing method I had used
| previously) suddenly was bestowed upon me.

I remember this anecdote because when I first read it, a zen-like 
understanding of seq suddenly was bestowed upon /me/. Maybe it should be in 
the docs. :-)


-- Ben

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


[Haskell-cafe] Re: Haskell code for this example of flow control

2006-02-04 Thread Dominic Steinitz
Here are some even older discussions on the subject. I don't know if anyone 
ever put them into a library or on the wiki.

Dominic.

http://haskell.org/pipermail/haskell-cafe/2005-May/009784.html

http://www.haskell.org//pipermail/libraries/2005-February/003143.html

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


[Haskell-cafe] does haskell have plist's ?

2006-02-04 Thread raptor
does Haskell have a property lists. Like Lisp ?
any pointer to examples ?

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


[Haskell-cafe] Why is $ right associative instead of left associative?

2006-02-04 Thread Brian Hulley

Hi -
In the Haskell98 report section 4.4.2 $ is specified as being right 
associative. This means that f $ a0 a1 $ b0 b1 would parse as f (a0 a1 (b0 
b1)) which seems rather strange to me. Surely it would be much more useful 
if $ were defined as left associative so that it could be used to separate 
the args to f?


Does anyone know why this strange associativity was chosen?

Thanks, Brian.

(The reason I'm asking is that I'm working on the syntax of a language 
similar to Haskell but which uses layout to allow expressions like:


f #$ -- can be followed by an explicit 
block or layout block

   a0 a1
   b0 b1

which is sugar for (f $ a0 a1) $ b0 b1 ie f (a0 a1) (b0 b1) ) and I was 
surprised to discover that the parentheses are needed for the most obvious 
reading) 


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


Re: [Haskell-cafe] Why is $ right associative instead of left associative?

2006-02-04 Thread Tomasz Zielonka
On Sat, Feb 04, 2006 at 02:52:20PM -, Brian Hulley wrote:
 Hi -
 In the Haskell98 report section 4.4.2 $ is specified as being right 
 associative. This means that f $ a0 a1 $ b0 b1 would parse as f (a0 a1 (b0 
 b1)) which seems rather strange to me. Surely it would be much more useful 
 if $ were defined as left associative so that it could be used to separate 
 the args to f?
 
 Does anyone know why this strange associativity was chosen?

Probably it was anticipated that right associative version will
be more useful. You can use it to create a chain of transformations,
similar to a chain of composed functions:

(f . g . h) x   =   f $ g $ h $ x

Example:

map f $ group $ sort $ filter g $ l

But of course, left associative version can also be useful. Some
time ago I used a left associative version of the strict application
operator, which I named (!$).

Anyway, you can't always remove all parentheses. And why would you want
to? Everybody is used to them.

Best regards
Tomasz

-- 
I am searching for programmers who are good at least in
(Haskell || ML)  (Linux || FreeBSD || math)
for work in Warsaw, Poland
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] does haskell have plist's ?

2006-02-04 Thread J. Garrett Morris
On 2/4/06, raptor [EMAIL PROTECTED] wrote:
 does Haskell have a property lists. Like Lisp ?
 any pointer to examples ?

Not built in to the language.  It's not hard to get the same
functionality though - I've attached a module that takes a (not
tremendously elegant) approach to the same thing, though.  You'll have
to store PLists explicitly, though, and this requires GHC.

 /g

--
We have lingered in the chambers of the sea 
By sea-girls wreathed with seaweed red and brown
Till human voices wake us, and we drown.
{-# OPTIONS_GHC -fglasgow-exts #-}
module PList (Property, lookup, cons, delete) where

import Data.Typeable

import Prelude hiding (lookup)

class Typeable t = Property a t | a - t
where label :: a - String
  value :: a - t

data AnyProperty 
where AnyProperty :: Property a t = a - AnyProperty

instance Property (String, Int) Int
where label = fst
  value = snd

instance Property (String, String) String
where label = fst
  value = snd

app :: (forall a t. Property a t = a - r) - AnyProperty - r
f `app` (AnyProperty p) = f p

type PList = [AnyProperty]

lookup :: Typeable a = String - PList - Maybe a
lookup prop pl | [anyProp] - property = (cast . value) `app` anyProp
   | otherwise = Nothing
where property = filter ((prop ==) . (label `app`)) pl

cons :: Property a t = a - PList - PList
cons = (:) . AnyProperty

delete :: String - PList - PList
delete prop pl = filter ((prop /=) . (label `app`)) pl___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is $ right associative instead of left associative?

2006-02-04 Thread Brian Hulley

Tomasz Zielonka wrote:

On Sat, Feb 04, 2006 at 02:52:20PM -, Brian Hulley wrote:

Hi -
In the Haskell98 report section 4.4.2 $ is specified as being right
associative. This means that f $ a0 a1 $ b0 b1 would parse as f (a0
a1 (b0 b1)) which seems rather strange to me. Surely it would be
much more useful if $ were defined as left associative so that it
could be used to separate the args to f?

Does anyone know why this strange associativity was chosen?


Probably it was anticipated that right associative version will
be more useful. You can use it to create a chain of transformations,
similar to a chain of composed functions:

   (f . g . h) x   =   f $ g $ h $ x

Example:

   map f $ group $ sort $ filter g $ l

But of course, left associative version can also be useful. Some
time ago I used a left associative version of the strict application
operator, which I named (!$).


I wonder if anyone has done empirical studies to determine scientifically 
which associativity would be more useful in practice eg by analysis of 
source code involving $ and comparing the number of parentheses that would 
be needed in each case, and perhaps also some studies involving the number 
of confused readers in each case...


Even though both versions are useful, it seems to me that faced with the 
choice of choosing an associativity for an operator that does function 
application, and given that prefix application is left associative, there is 
one clear winner, but unfortunately the Haskell committee didn't see it this 
way, and perhaps it is too late to ever change this (just like :: and : 
which were mixed up for reasons unknown). Especially since chains can 
already be composed using . .




Anyway, you can't always remove all parentheses. And why would you
want to? Everybody is used to them.


$'s advertised purpose is to remove parentheses, but I agree that 
parenthesized code is often more readable (especially when operators have 
unexpected fixities... :-))


Regards, Brian. 


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


Re: [Haskell-cafe] Re[2]: strict Haskell dialect

2006-02-04 Thread Jan-Willem Maessen


On Feb 3, 2006, at 8:16 PM, Brian Hulley wrote:


Jan-Willem Maessen wrote:


I pointed out some problems with strict Haskell in a recent talk, but
I think it'd be worth underscoring them here in this forum.


Is the text of this talk or points raised in it available online  
anywhere?


snip There is one very difficult piece of syntax in a strict  
setting: The

*where* clause.  The problem is that it's natural to write a bunch of
bindings in a where clause which only scope over a few conditional
clauses.  I'm talking about stuff like this:

f x
  | p x   = . a ...a . a  a ...
  | complex_condition = . b .. b ... b ..
  | otherwise = . a ... b .
  where a = horrible expression in x which is bottom when
complex_condition is true.
b = nasty expression in x which doesn't terminate when p x
is true.
complex_condition = big expression which
 goes on for lines and lines
 and would drive the reader
 insane if it occurred in line.


Surely it would not be too difficult for the compiler to only  
evaluate the where bindings that are relevant depending on which  
guard evaluates to True ie in your example, the binding for a would  
be evaluated if p x is True, otherwise the complex_condition would  
be evaluated, and if True, b would be evaluated, otherwise a and b  
would be evaluated: ...


In principle, yes, this is eminently doable.  But the translation  
becomes surprisingly messy when the bindings in question are mutually  
recursive.  Certainly it's not a simple syntax-directed translation,  
in contrast to essentially every other piece of syntactic sugar in  
the language.


-Jan-Willem Maessen

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


Re: [Haskell-cafe] Why is $ right associative instead of left associative?

2006-02-04 Thread Taral
On 2/4/06, Brian Hulley [EMAIL PROTECTED] wrote:
 Does anyone know why this strange associativity was chosen?

I think it's very natural. Everything after the $, including other $
expressions, is applied to the stuff before the $. This saves me from
a lot of nested parentheses.

It seems to be that the left-associative version of $ does not
decrease nesting level so effectively.

--
Taral [EMAIL PROTECTED]
Computer science is no more about computers than astronomy is about
telescopes.
-- Edsger Dijkstra
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is $ right associative instead of leftassociative?

2006-02-04 Thread Brian Hulley

Brian Hulley wrote:

Tomasz Zielonka wrote:

On Sat, Feb 04, 2006 at 02:52:20PM -, Brian Hulley wrote:

Hi -
In the Haskell98 report section 4.4.2 $ is specified as being right
associative. This means that f $ a0 a1 $ b0 b1 would parse as f (a0
a1 (b0 b1)) which seems rather strange to me. Surely it would be
much more useful if $ were defined as left associative so that it
could be used to separate the args to f?

Does anyone know why this strange associativity was chosen?


Probably it was anticipated that right associative version will
be more useful. You can use it to create a chain of transformations,
similar to a chain of composed functions:

   (f . g . h) x   =   f $ g $ h $ x


Actually I'm beginning to think this might be more useful after all.



Example:

   map f $ group $ sort $ filter g $ l

But of course, left associative version can also be useful. Some
time ago I used a left associative version of the strict application
operator, which I named (!$).


I suppose I could use $$ for left associative application, and #$$ for 
layout application.




I wonder if anyone has done empirical studies to determine
scientifically which associativity would be more useful in practice
eg by analysis of source code involving $ and comparing the number of
parentheses that would be needed in each case, and perhaps also some
studies involving the number of confused readers in each case...

Even though both versions are useful, it seems to me that faced with
the choice of choosing an associativity for an operator that does
function application, and given that prefix application is left
associative, there is one clear winner, but unfortunately the Haskell
committee didn't see it this way, and perhaps it is too late to ever
change this (just like :: and : which were mixed up for reasons
unknown). Especially since chains can already be composed using . .


It would be very useful if the Haskell report explained *why* decisions were 
made, because there often seem to be good reasons that are not immediately 
obvious and sometimes counter intuitive. I think the mystery surrounding :: 
and : might have been that originally people thought type annotations would 
hardly ever be needed whereas list cons is often needed, but now that it is 
regarded as good practice to put a type annotation before every top level 
value binding, and as the type system becomes more and more complex (eg with 
GADTs etc), type annotations are now presumably far more common than list 
cons so it would be good if Haskell Prime would swap these operators back to 
their de facto universal inter-language standard of list cons and type 
annotation respectively.


Regards, Brian. 


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


Re: [Haskell-cafe] Why is $ right associative instead of left associative?

2006-02-04 Thread Stefan Holdermans

Taral wrote:


I think it's very natural. Everything after the $, including other $
expressions, is applied to the stuff before the $. This saves me from
a lot of nested parentheses.


To me, ($) helping me to avoid writing lots of parentheses, makes it  
extremely useful. Actually: except for passing function application  
to higher-order functions, this is the only way I use it. So, I  
always thought parentheses were *the* reason for the right- 
associativity of ($). Not sure if it really was originally, but, ever  
so, I think it is the best reason.


Regards,

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


Re: [Haskell-cafe] Why is $ right associative instead of leftassociative?

2006-02-04 Thread Tomasz Zielonka
On Sat, Feb 04, 2006 at 07:15:47PM -, Brian Hulley wrote:
 I think the mystery surrounding :: and : might have been that
 originally people thought type annotations would hardly ever be needed
 whereas list cons is often needed, but now that it is regarded as good
 practice to put a type annotation before every top level value
 binding, and as the type system becomes more and more complex (eg with
 GADTs etc), type annotations are now presumably far more common than
 list cons so it would be good if Haskell Prime would swap these
 operators back to their de facto universal inter-language standard of
 list cons and type annotation respectively.

I am not convinced. Even if you really want to write types for every
top-level binding, it's only one :: per binding, which can have a
definition spanning for many lines and as complicated type as you
want. On the other hand, when you are doing complicated list processing,
it is not uncommon to have four (or more) :'s per _line_.

Personally, I started my FP adventure with OCaml (which has the thing
the other way around), and I felt that the meanings of :: and : should
be reversed - before I even knew Haskell!

Best regards
Tomasz

-- 
I am searching for programmers who are good at least in
(Haskell || ML)  (Linux || FreeBSD || math)
for work in Warsaw, Poland
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is $ right associative instead of left associative?

2006-02-04 Thread Tomasz Zielonka
On Sat, Feb 04, 2006 at 08:37:51PM +0100, Stefan Holdermans wrote:
 Taral wrote:
 
 I think it's very natural. Everything after the $, including other $
 expressions, is applied to the stuff before the $. This saves me from
 a lot of nested parentheses.
 
 To me, ($) helping me to avoid writing lots of parentheses, makes it  
 extremely useful. Actually: except for passing function application  
 to higher-order functions, this is the only way I use it. So, I  
 always thought parentheses were *the* reason for the right- 
 associativity of ($). Not sure if it really was originally, but, ever  
 so, I think it is the best reason.

A left-associative low-precedence application operator can also help
avoid writing parentheses, only in different cases, eg.

f $$ x + 1 $$ x * x + 2 * x + 1

equals

f (x + 1) (x * x + 2 * x + 1)

But in this case the parentheses don't nest, which may be a reason
why a right-associative version was chosen. ($) helps to avoid
the case of nesting parentheses. Such nesting is unbounded, for
example you can have chains like this with arbitrary length:

a (b (c (d (e (f x)

even if you only have unary functions.

Also, adding or removing a function in such a chain can require
non-local changes, that is you are forced to add or remove a closing
parenthesis on the end of expression.

If you use ($):

a $ b $ c $ d $ e $ f x

you can easily add or remove a function in the chain.

On the other hand, adding new parameters to calls like this

f (x + 1) (y - 1) ...

is very localised.

Best regards
Tomasz

-- 
I am searching for programmers who are good at least in
(Haskell || ML)  (Linux || FreeBSD || math)
for work in Warsaw, Poland
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is $ right associative instead of leftassociative?

2006-02-04 Thread Stefan Holdermans

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Brian wrote:


I think the mystery surrounding :: and : might have been that
originally people thought type annotations would hardly ever be needed
whereas list cons is often needed, but now that it is regarded as good
practice to put a type annotation before every top level value
binding, and as the type system becomes more and more complex (eg with
GADTs etc), type annotations are now presumably far more common than
list cons so it would be good if Haskell Prime would swap these
operators back to their de facto universal inter-language standard of
list cons and type annotation respectively.


I don't think Haskell Prime should be about changing the look and  
feel of the language.


Regards,

  Stefan
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.1 (Darwin)

iD8DBQFD5RSuX0lh0JDNIpwRAocIAKCvxR4PujkceRo94NgbeCLFbAwwNgCfZl+6
ncz3/uxwGbmsAUe76oWDgGA=
=pVEw
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is $ right associative instead of leftassociative?

2006-02-04 Thread Brian Hulley

Tomasz Zielonka wrote:

On Sat, Feb 04, 2006 at 07:15:47PM -, Brian Hulley wrote:

I think the mystery surrounding :: and : might have been that
originally people thought type annotations would hardly ever be
needed whereas list cons is often needed, but now that it is
regarded as good practice to put a type annotation before every top
level value binding, and as the type system becomes more and more
complex (eg with GADTs etc), type annotations are now presumably far
more common than list cons so it would be good if Haskell Prime
would swap these operators back to their de facto universal
inter-language standard of list cons and type annotation
respectively.


I am not convinced. Even if you really want to write types for every
top-level binding, it's only one :: per binding, which can have a
definition spanning for many lines and as complicated type as you
want. On the other hand, when you are doing complicated list
processing, it is not uncommon to have four (or more) :'s per _line_.


I wonder if extending the sugared list syntax would help here. The | symbol 
is used for list comprehensions but something along the lines of:


   [a,b,c ; tail]  ===  a :: b :: c :: tail -- where :: 
means list cons


then there would seldom be any need to use the list cons symbol anywhere 
except for sections. I would use , instead of ; in the block syntax so 
that ; could be freed for the above use and so that there would be a 
generic block construct {,,,} that could be used for records also (and could 
always be replaced by layout) eg


   P {x=5, y=6}

could be written also as

   P #-- # allows a layout block to be started
 x = 5
 y = 6



Personally, I started my FP adventure with OCaml (which has the thing
the other way around), and I felt that the meanings of :: and : should
be reversed - before I even knew Haskell!


I see what you mean ;-). However the swapping of :: and : really is very 
confusing when one is used to things being the other way round. Also in 
natural language, : seems to have a much closer resonance with the 
type/kind annotation meaning than with constructing a list. I also wonder if 
it is such a good idea to make lists so special? Does this influence our 
thinking subconciously to use list-based solutions when some other data 
structure may be better?


Regards, Brian. 


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


Re: [Haskell-cafe] Why is $ right associative instead of leftassociative?

2006-02-04 Thread Brian Hulley

Stefan Holdermans wrote:

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Brian wrote:


I think the mystery surrounding :: and : might have been that
originally people thought type annotations would hardly ever be
needed whereas list cons is often needed, but now that it is
regarded as good practice to put a type annotation before every top
level value binding, and as the type system becomes more and more
complex (eg with GADTs etc), type annotations are now presumably far
more common than list cons so it would be good if Haskell Prime
would swap these operators back to their de facto universal
inter-language standard of list cons and type annotation
respectively.


I don't think Haskell Prime should be about changing the look and
feel of the language.


Perhaps it is just a matter of aesthetics about :: and :, but I really feel 
these symbols have a de-facto meaning that should have been respected and 
that Haskell Prime would be a chance to correct this error. However no doubt 
I'm alone in this view so fair enough - it's just syntax after all and I can 
run my own programs through a pre-processor if I want them the other way 
round... :-)


Regards, Brian. 


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


Re: [Haskell-cafe] Why is $ right associative instead of leftassociative?

2006-02-04 Thread Paul Hudak
Actually, one of the main reasons that we chose (:) is that that's what 
Miranda used.  So, at the time at least, it was not entirely clear what 
the de facto universal inter-language standard was.


In any case, I agree with Stefan regarding Haskell Prime!

  -Paul


Stefan Holdermans wrote:

Brian wrote:


I think the mystery surrounding :: and : might have been that
originally people thought type annotations would hardly ever be needed
whereas list cons is often needed, but now that it is regarded as good
practice to put a type annotation before every top level value
binding, and as the type system becomes more and more complex (eg with
GADTs etc), type annotations are now presumably far more common than
list cons so it would be good if Haskell Prime would swap these
operators back to their de facto universal inter-language standard of
list cons and type annotation respectively.


I don't think Haskell Prime should be about changing the look and  feel 
of the language.


Regards,

  Stefan

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


Re: [Haskell-cafe] does haskell have plist's ?

2006-02-04 Thread Bulat Ziganshin
Hello raptor,

Saturday, February 04, 2006, 7:06:39 PM, you wrote:

r does Haskell have a property lists. Like Lisp ?
r any pointer to examples ?

no. Haskell data values don't carry any invisible information besides
of lazyness. in this aspect Haskell is like other compiled languages
like C where int is just CPU-level integer what is just 4 bytes and
nothing more (while Lisp is like other interpreted languages)

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re[2]: [Haskell-cafe] request for help

2006-02-04 Thread Bulat Ziganshin
Hello Marco,

Saturday, February 04, 2006, 4:39:23 PM, you wrote:

MAFdA Hello.
MAFdA English is not my native language (I'm Portuguese).
MAFdA The haskell-cafe mailing list is usually very active and subscribers
MAFdA do help each other, so I believe you will not have any trouble in
MAFdA finding real Englishmen who will read and correct the document ;-)

thank you. J.P. Bernardy already corrected a part, so i think that Englishmens
will help me

MAFdA However, if by any chance you don't, please let me know and I will do it
MAFdA (just tell me how, because the wiki is password-protected).

you just need to register itself in this Wiki system. look at the
register text on the page, i don't remember exact. or may be login,
where you will have chance to register

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re: [Haskell-cafe] Why is $ right associative instead of leftassociative?

2006-02-04 Thread Cale Gibbard
On 04/02/06, Brian Hulley [EMAIL PROTECTED] wrote:
 Stefan Holdermans wrote:
  -BEGIN PGP SIGNED MESSAGE-
  Hash: SHA1
 
  Brian wrote:
 
  I think the mystery surrounding :: and : might have been that
  originally people thought type annotations would hardly ever be
  needed whereas list cons is often needed, but now that it is
  regarded as good practice to put a type annotation before every top
  level value binding, and as the type system becomes more and more
  complex (eg with GADTs etc), type annotations are now presumably far
  more common than list cons so it would be good if Haskell Prime
  would swap these operators back to their de facto universal
  inter-language standard of list cons and type annotation
  respectively.
 
  I don't think Haskell Prime should be about changing the look and
  feel of the language.

 Perhaps it is just a matter of aesthetics about :: and :, but I really feel
 these symbols have a de-facto meaning that should have been respected and
 that Haskell Prime would be a chance to correct this error. However no doubt
 I'm alone in this view so fair enough - it's just syntax after all and I can
 run my own programs through a pre-processor if I want them the other way
 round... :-)

 Regards, Brian.


In Haskell, they have a de-facto meaning which is opposite to the one
you're talking about :) Besides, lots of papers and various other
programming languages use Haskell's convention (which was taken from
Miranda).

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


Re: [Haskell-cafe] Why is $ right associative instead of leftassociative?

2006-02-04 Thread Jared Updike
 [a,b,c ; tail]  ===  a :: b :: c :: tail -- where ::

How is [a,b,c ; tail]   simpler, clearer or less typing than 
a:b:c:tail  ? I think that the commas and semicolons are easy to
confuse.

While we're talking about the aesthetics of :: and :, I like how a
line with a type annotation stands out strongly with ::, e.g.
map :: (a - b) - [a] - [b]
Compare this to
map : (a - b) - [a] - [b]
where the identifier looks more connected to the type. You will notice
this is different than ML anyway because in Haskell you can separate
the type annotation and the declaration.

If you are designing your own langauge, you will of course have your
own aesthetics and reasons for doing it your way. As for me, I started
to design (in my head) the perfect language (for me), but the more I
learned and used Haskell, the more I realized how carefully designed
it was and how it was better for me to use my efforts to learn from
Haskell (especially conceptually, since the syntax is so transparent
and the ideas are so amazing) than to try to insert clever ideas to
satisfy my own whims. Sure, there are always little things to nitpick,
but on the whole, can you think of more succinct language with more
power? (and less parentheses!) Plus, what other languages let you more
easily add (infix) operators, etc. and change things to fit your whim,
anyway (and still be strongly type!).

Cheers,
  Jared.
--
http://www.updike.org/~jared/
reverse )-:
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is $ right associative instead of leftassociative?

2006-02-04 Thread Chris Kuklewicz
Brian Hulley wrote:
 Jared Updike wrote:
 [a,b,c ; tail]  ===  a :: b :: c :: tail --
 where ::

 How is [a,b,c ; tail]   simpler, clearer or less typing than
 a:b:c:tail  ? I think that the commas and semicolons are easy to
 confuse.
 
 It seems strange that you can write [a,b,c] with a nice list sugar but
 if you want to include a tail you have to switch to the infix notation
 using list cons. Prolog for example allows you to write [a,b,c|Tail] but
 neither Haskell nor ML allows this. In Haskell, | is used to introduce a
 list comprehension so I was just trying to find a replacement symbol for
 when you want the equivalent of the Prolog list sugar so that you
 wouldn't be forced to use infix notation.
 
 All this was not to replace a:b:c:tail but was to replace a::b::c::tail
 so that : could be used for type annotations instead.
 

There is the .. operator which is unused in pattern matching contexts. So maybe

case [1,3..] of
  [a,b,c,tail..] - tail   -- I like this one, the ..] catches the eye better
  [a,b,c,..tail] - tail   -- I think this is less clear at a glance
  [a,b,c,..tail..] - tail -- I expect no one to like this
  [a,b,c,_..] - [a,b,c]   -- Not the best looking thing I've ever seen
  [a,b,c,.._] - [a,b,c]   -- ditto
  [a,b,c,.._..] - [a,b,c] -- ick

But this implies [a,b,c,[]..] is the same as [a,b,c] and [a,b,c,[d,e,f]..] is
the same as [a,b,c,d,e,f] and [a,b,c,[d,e,f..]..] is [a,b,c,d,e,f..]

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


Re: [Haskell-cafe] Why is $ right associative instead of leftassociative?

2006-02-04 Thread Bill Wood
On Sat, 2006-02-04 at 23:34 +, Chris Kuklewicz wrote:
   . . .
 But this implies [a,b,c,[]..] is the same as [a,b,c] and [a,b,c,[d,e,f]..] is
 the same as [a,b,c,d,e,f] and [a,b,c,[d,e,f..]..] is [a,b,c,d,e,f..]

Hmmm, does this get us to difference lists ala Prolog?

 -- Bill Wood


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


Re: [Haskell-cafe] Why is $ right associative instead of left associative?

2006-02-04 Thread ajb
G'day all.

Quoting Tomasz Zielonka [EMAIL PROTECTED]:

 Probably it was anticipated that right associative version will
 be more useful. You can use it to create a chain of transformations,
 similar to a chain of composed functions:

 (f . g . h) x   =   f $ g $ h $ x

Of course, if $ were left-associative, it would be no less useful here,
because you could express this chain thusly:

f . g . h $ x

This is the way that I normally express it.  Partly because I find
function application FAR more natural than right-associative application,
and partly because I'm hedging my bets for Haskell 2 just in case the
standards committee wakes up and notices that the associativity of $ is
just plain wrong and decides to fix it. :-)

In fact, I'll go out on a limb and claim that ALL such uses of $ are
better expressed with composition.  Anyone care to come up with a
counter-example?

 But of course, left associative version can also be useful. Some
 time ago I used a left associative version of the strict application
 operator, which I named (!$).

In fact, I think it's much MORE useful, and for precisely the reason
that you state: it makes strict application much more natural.

Strict application also has the wrong associativity.  As it is, $! is
only useful if the _last_ argument of a function needs to be strict.  I
find that ordering my arguments in a de Bruijn-like order (which many
experienced functional programmers do unconsciously) results in this
being the least common case.

The last argument of a function is usually the induction argument: it's
almost invariably the subject of a top-level test.  The strictness
analyser invariably picks up that the argument is strict.  It's the OTHER
arguments you may need to evaluate early.

Suppose you have a function with three arguments, the second of which
needs to be strict.  I want to write something like this:

f (g x) $! (h y) $ (j z)

What I have to write is this:

(f (g x) $! (h y)) (j z)

or this:

let y' = h y in y' `seq` f (g x) y' (j z)

 Anyway, you can't always remove all parentheses. And why would you want
 to? Everybody is used to them.

I agree.  However, sometimes parentheses make things more confusing.
Almost always the best solution is to give the offending subexpression
a name, using let or where.  However, the specific case above is the
only one that I've found where this, too, makes things worse.

In summary: There is no good reason to make $ right-associative and at
least one good reason to make it left-associative.

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is $ right associative instead of leftassociative?

2006-02-04 Thread ajb
G'day all.

Quoting Paul Hudak [EMAIL PROTECTED]:

 Actually, one of the main reasons that we chose (:) is that that's what
 Miranda used.  So, at the time at least, it was not entirely clear what
 the de facto universal inter-language standard was.

Exactly.  One point that's often not appreciated is that Haskell is not
a descendent of ML.  The ML lineage is, roughly:

Lisp - ISWIM - ML - SML, LML, O'Caml etc

And the Haskell lineage is:

Lisp - ISWIM - SASL - KRC - Miranda - Haskell

ML is much more like an older cousin than an ancestor.

This point is important because Turner languages already had a list
syntax at the time that they adopted an ML-like type system.

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is $ right associative instead of left associative?

2006-02-04 Thread ajb
G'day all.

Quoting [EMAIL PROTECTED]:

 This is the way that I normally express it.  Partly because I find
 function application FAR more natural than right-associative application,

I meant to say that I find function COMPOSITION more natural than
right-associative application.  It certainly fits better with my
personal biases about good functional programming style.

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is $ right associative instead of leftassociative?

2006-02-04 Thread Brian Hulley

[EMAIL PROTECTED] wrote:

G'day all.

Quoting [EMAIL PROTECTED]:


This is the way that I normally express it.  Partly because I find
function application FAR more natural than right-associative
application,


I meant to say that I find function COMPOSITION more natural than
right-associative application.  It certainly fits better with my
personal biases about good functional programming style.


Yes the case you've made for $ being left associative is very compelling - 
namely that the existing associativity actively encourages a *bad* 
programming style in which the right associative $ hides the composition in 
a chain of function applications instead of allowing the composition to be 
explicit and neatly separate from its argument.


Moreover, the existing associativity of $ implies that whoever thought it up 
was confusing two concepts: application and composition, instead of allowing 
$ to take its proper place as an equal citizen to ., with the 
associativity proper to its role as application alone.


Thus if $ were made left associative in Haskell Prime, this would add 
clarity to the thought forms associated with the language, which would 
(presumably) in turn lead to better programs being written in it.


Regards, Brian.


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


[Haskell-cafe] Re: Why is $ right associative instead of left associative?

2006-02-04 Thread Ben Rudiak-Gould
No one has mentioned yet that it's easy to change the associativity of $ 
within a module in Haskell 98:


import Prelude hiding (($))

infixl 0 $
f$x = f x

or, for the purists,

import Prelude hiding (($))
import qualified Prelude (($))

infixl 0 $
($) = (Prelude.$)

-- Ben

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


Re: [Haskell-cafe] Why is $ right associative instead of leftassociative?

2006-02-04 Thread Joseph H. Fasel III
These lineages are more or less right, except that there is a bit of
incest: LML is certainly one of the progenitors of Haskell.  (more
semantically than syntactically, though)

Cheers,
--Joe

[EMAIL PROTECTED] said:
 G'day all.

 Quoting Paul Hudak [EMAIL PROTECTED]:

 Actually, one of the main reasons that we chose (:) is that that's what
 Miranda used.  So, at the time at least, it was not entirely clear what
 the de facto universal inter-language standard was.

 Exactly.  One point that's often not appreciated is that Haskell is not
 a descendent of ML.  The ML lineage is, roughly:

 Lisp - ISWIM - ML - SML, LML, O'Caml etc

 And the Haskell lineage is:

 Lisp - ISWIM - SASL - KRC - Miranda - Haskell

 ML is much more like an older cousin than an ancestor.

 This point is important because Turner languages already had a list
 syntax at the time that they adopted an ML-like type system.

 Cheers,
 Andrew Bromage
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe



Joseph H. Fasel, Ph.D.  email: [EMAIL PROTECTED]
Stockpile-Complex Modeling and Analysis phone: +1 505 667 7158
University of Californiafax: +1 505 667 2960
Los Alamos National Laboratory  post: D-2 MS F609; Los Alamos, NM
87545

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


Re: [Haskell-cafe] Haskell to call Microsoft COM (Dispatch)

2006-02-04 Thread Marsh J. Ray

Marc Weber wrote:

Hi. I spent much time trying to get it to work.. you have to download
the whole fptools directory (from cvs!).. and I think i did some little
patches but I can check out again and compare..
It did compile and I think it's working well but I'm still struggling
getting to use it.. At least the examples do compile!

If you are really interested I would appreciate getting in contact with
you (my private email: marco-oweber a t gmx.de) .. Perhaps we can help
each other. (Becaue I'm not an experienced haskell programmer, yet ;-) 
I've been trying to get hdirect to build and would also appreciate any 
hints. Sounds like I should try the version from CVS?


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