Re: [Haskell-cafe] Where does ~> come from?

Am Dienstag, 19. Februar 2008 18:26 schrieben Sie:
[…]
However, I was told this: ~> a b is a ~> b, but if I write c a b and wish the effect of a `c` b. This would not work. ~> as an infix operator has a special place in GHC. It is not "just a type variable".
Sorry, but I don’t understand fully what you mean. :-( But nevertheless, a ~> b is not the same as ~> a b but as (~>) a b. It’s just like with ordinary operators where a + b is the same as (+) a b. ~> is not special in GHC. You could use, for example, ### instead of ~> and get the same results. However, GHC accepts type operators only if you tell it to do so. Give GHC the option -XTypeOperators or insert {-# LANGUAGE TypeOperators #-} at the beginning of your source file.
[…]
Best wishes, Wolfgang

On Feb 19, 2008 4:15 PM, Wolfgang Jeltsch
Am Dienstag, 19. Februar 2008 18:26 schrieben Sie:
[…]
However, I was told this: ~> a b is a ~> b, but if I write c a b and wish the effect of a `c` b. This would not work. ~> as an infix operator has a special place in GHC. It is not "just a type variable".
Sorry, but I don't understand fully what you mean. :-( But nevertheless, a ~> b is not the same as ~> a b but as (~>) a b. It's just like with ordinary operators where a + b is the same as (+) a b.
Note that some (all?) versions of GHC will incorrectly print "a ~> b"
as "~> a b".
http://hackage.haskell.org/trac/ghc/ticket/1930
Prelude> :t undefined :: a + b
undefined :: a + b :: forall (+ :: * -> * -> *) a b. + a b
It mostly gets infix type constructors right, although there are
apparently problems with precedence and associativity.
--
Dave Menendez

If ~> does not have any special meaning and it could be ### or xyz,
then how does GHC know to print
a ~> b, but not ~> a b
a ### b, but not ### a b
xyz a b, but not a `xyz` b
Simply because xyz is alphanumeric?
On Wed, Feb 20, 2008 at 12:34 AM, David Menendez
On Feb 19, 2008 4:15 PM, Wolfgang Jeltsch
wrote: Am Dienstag, 19. Februar 2008 18:26 schrieben Sie:
[…]
However, I was told this: ~> a b is a ~> b, but if I write c a b and wish the effect of a `c` b. This would not work. ~> as an infix operator has a special place in GHC. It is not "just a type variable".
Sorry, but I don't understand fully what you mean. :-( But nevertheless, a ~> b is not the same as ~> a b but as (~>) a b. It's just like with ordinary operators where a + b is the same as (+) a b.
Note that some (all?) versions of GHC will incorrectly print "a ~> b" as "~> a b".
http://hackage.haskell.org/trac/ghc/ticket/1930
Prelude> :t undefined :: a + b undefined :: a + b :: forall (+ :: * -> * -> *) a b. + a b
It mostly gets infix type constructors right, although there are apparently problems with precedence and associativity.
-- Dave Menendez
http://www.eyrie.org/~zednenem/ _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Wed, Feb 20, 2008 at 07:18:42PM -0500, Steve Lihn wrote:
If ~> does not have any special meaning and it could be ### or xyz, then how does GHC know to print a ~> b, but not ~> a b a ### b, but not ### a b xyz a b, but not a `xyz` b
Simply because xyz is alphanumeric?
Yes. Stefan

Stefan O'Rear wrote:
On Wed, Feb 20, 2008 at 07:18:42PM -0500, Steve Lihn wrote:
If ~> does not have any special meaning and it could be ### or xyz, then how does GHC know to print a ~> b, but not ~> a b a ### b, but not ### a b xyz a b, but not a `xyz` b
Simply because xyz is alphanumeric?
Yes.
To slightly elaborate this: In Haskell, normal (prefix) functions and operators (infix) functions are syntactically distinguished by the characters they may contain: the former must contain only alphanumerics plus ' and _, the latter only operator symbols such as !#$%&*+./<=>?@\^|-~ for details see the Haskell98 Report (http://www.haskell.org/onlinelibrary/lexemes.html). Cheers Ben
participants (5)
-
Ben Franksen
-
David Menendez
-
Stefan O'Rear
-
Steve Lihn
-
Wolfgang Jeltsch