Re: Alternatives to . for composition

2006-03-27 Thread Josef Svenningsson
FYI, Cayenne used the center dot as composition. See the System$HO module.
http://www.cs.chalmers.se/~augustss/cayenne/system.html
I remember liking it but I think the ring operator would be closer to
mathematics notation and indeed the best choice.

Cheers,

/Josef

On 3/25/06, Dylan Thurston [EMAIL PROTECTED] wrote:
 At http://hackage.haskell.org/trac/haskell-prime/wiki/CompositionAsDot ,
 there is a list of possible Unicode replacements for the '.'
 operator.  Oddly, the canonical one is missing (from
 http://www.unicode.org/charts/PDF/U2200.pdf ):

 2218  RING OPERATOR
   = composite function
   = APL jot
 00B0 degree sign
 25E6 white bullet

 I don't think any other Unicode character should be considered.

 (Is this the approved way to send minor updates like this?)

 Peace,
 Dylan Thurston


 -BEGIN PGP SIGNATURE-
 Version: GnuPG v1.4.1 (GNU/Linux)

 iD8DBQFEJXsQVeybfhaa3tcRApNiAJ9eSfuIgaRkbJaOle1IG5AmzWoOfACdH9U1
 Vh/63jQ4c0Rft041WGEbut8=
 =HF0S
 -END PGP SIGNATURE-


 ___
 Haskell-prime mailing list
 Haskell-prime@haskell.org
 http://haskell.org/mailman/listinfo/haskell-prime



___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Strict tuples

2006-03-21 Thread Josef Svenningsson
On 3/21/06, Simon Marlow [EMAIL PROTECTED] wrote:
By all means have strict tuples in a library somewhere.They don't needto have special syntax.I have a module Data.Pair which provides pairs with different strictness properties. Perhaps it can be used as a startingpoint.
Cheers,/Josef
-
-- |
-- Module  :  Data.Pair
-- Copyright   :  (c) Josef Svenningsson 2005
-- License :  BSD-style
--
-- Maintainer  :  [EMAIL PROTECTED]
-- Stability   :  experimental
-- Portability :  portable
--
-- Several pair data types with different strictness properties
--
--
module Data.Pair ( Pair(..),
		   StrictLeft(..),
		   StrictRight(..),
		   StrictPair(..)
		  ) where

-- |A class for pairs. We need this to have a consistent interface for
--  several different pair types with different strictness properties.
--  Minimal complete instances are either @first@, @second@ and @pair@
--  or @casePair@ and @[EMAIL PROTECTED]
class Pair p where
  first:: p a b - a
  first p  = casePair (\a _ - a)
  second   :: p a b - b
  second p = casePair (\_ b - b)
  casePair :: (a - b - c) - p a b - c
  casePair c p = c (first p) (second p)
  pair :: a - b - p a b

propPair p = p == pair (first p) (second p)

data StrictLeft  a b = StrictLeft !a  b
data StrictRight a b = StrictRight a !b
data StrictPair  a b = StrictPair !a !b

instance Pair (,) where
  first  (f,_) = f
  second (_,s) = s
  pair f s = (f,s)

instance Pair StrictLeft where
  first  (StrictLeft f _) = f
  second (StrictLeft _ s) = s
  pair f s = StrictLeft f s

instance Pair StrictRight where
  first  (StrictRight f _) = f
  second (StrictRight _ s) = s
  pair f s = StrictRight f s

instance Pair StrictPair where
  first  (StrictPair f _) = f
  second (StrictPair _ s) = s
  pair f s = StrictPair f s
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: The worst piece of syntax in Haskell

2006-02-21 Thread Josef Svenningsson
On 2/22/06, Claus Reinke [EMAIL PROTECTED] wrote:
 class Monad m= MonadPlus mwhere ... class Ord a= Ix awhere ... instance Integral a= Eq (Ratio a)where ...
still difficult?-) works just as well when the constraint lists get longer.This is the style I've adopted and it makes things a little better but not much. I still found it difficult to browse through my library even with this kind of layout.
ps. I like that its the same way as for type signatures.
Well, it's good that the class contraint syntax for type signatures is consistent with that of class and instance declarations. But it is still the wrong syntax.Cheers,/Josef
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Comment Syntax

2006-02-02 Thread Josef Svenningsson
On 2/2/06, Henrik Nilsson [EMAIL PROTECTED] wrote:
Hi all,To corroborate Wadler's law further.:-) Josef wrote:
  Oh yes, it does happen that a single line comment begins with a  special symbol. It has happened to me on several occations when using  haddock annotation to my source code. It is all to easy to forget that
  extra space. With incomprehensible error messages as a result.But might that not just mean that the error messages ought to beimproved?I don't know how hard that would be, but after having played around
a bit with GHC, the messages I get are either of the typeparse error on input '--|' or of the type Not in scope: `--'(followed by lots of other stuff not being in scope etc).
If this really is a big problem for beginners, it would not seemtotally infeasible to add some special code that helpfully suggeststhat a space perhaps ought to be inserted?Or have you seen significantly worse error messages?
My point here was not that the error messages was that terrible. I just wanted to point out to Manuel that it does happen that single line comments start with a symbol. Which makes the current comment syntax somewhat awkward.
Cheers,/Josef
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Comment Syntax

2006-02-01 Thread Josef Svenningsson
On 2/2/06, John Meacham [EMAIL PROTECTED] wrote:
On Thu, Feb 02, 2006 at 02:31:32AM +0100, Josef Svenningsson wrote: I still think there is an inconsistency here. And it has to do with maximal munch lexing. Maximal munch is what we normally expect from a lexer for a
 programming language. But the way comments work at the moment breaks maximal munch. The longest possible read is to read the whole line as a comment and not interpret for instance --^ as an operator. It breaks any programmers'
 intuition not only beginners'. I still get it wrong from time to time.huh? this is exactly the opposite. maximal munch means that it wouldconsume everything and then interpret it as an operator. having it the
other way would be a special case because you would have to stopconsuming input after the first --.I new this response were coming It basically comes down to how one interprets the maximal munch. I know there are plenty of people who agree with you. But there are those that agree with my standpoint as well. I'm not going to propose that we start arguing about this. I suppose we'll have to use other arguments to persuade each other about the comment syntax.
/Josef
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime