Re: [Haskell-cafe] Infix tuple comma query (,)

2009-04-06 Thread Alexander Dunlap
On Mon, Apr 6, 2009 at 8:53 AM, Paul Keir  wrote:
> module Main where
>
>
>
> data (:%^&) a b = a :%^& b    deriving (Show)
>
>
>
> main = do
>
>   print $ 18 :%^& (Just 99)
>
>   print $ (,) 9 10
>
>   print $ 9 , 10
>
>
>
> The last line in the code above causes a compile error.
>
> Why does infix use of the comma (tuple constructor?) function fail without
> brackets?
>
>
>
> Thanks,
>
> Paul
>

When I want a lighter syntax for pairs (when doing a long list of
them, e.g.), I often define

(&) :: a -> b -> (a,b)
a & b = (a,b)

and then you can indeed write

print $ 1 & 2

(assuming you get precedence right).

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


Re: [Haskell-cafe] Infix tuple comma query (,)

2009-04-06 Thread Ryan Ingram
The prefix notation for
> \a b c -> (a,b,c)
is (,,)

Without the parentheses, it's not immediately clear whether
> foo $ a,b
means
> foo (a,b)
or
> foo (\c -> (a,b,c))
or some other, bigger tuple size.

Anyways, it's just syntax :)

  -- ryan


On Mon, Apr 6, 2009 at 9:08 AM, Daniel Fischer  wrote:
> Am Montag 06 April 2009 17:53:24 schrieb Paul Keir:
>> module Main where
>>
>>
>>
>> data (:%^&) a b = a :%^& b    deriving (Show)
>>
>>
>>
>> main = do
>>
>>   print $ 18 :%^& (Just 99)
>>
>>   print $ (,) 9 10
>>
>>   print $ 9 , 10
>>
>>
>>
>> The last line in the code above causes a compile error.
>>
>> Why does infix use of the comma (tuple constructor?) function fail
>> without brackets?
>>
>
> Tuples are special baked-in syntax. The parentheses are part of the tuple
> constructor(s).
> It may be confusing you that you can use it prefix as well as "aroundfix".
>
>>
>>
>> Thanks,
>>
>> Paul
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Infix tuple comma query (,)

2009-04-06 Thread Daniel Fischer
Am Montag 06 April 2009 17:53:24 schrieb Paul Keir:
> module Main where
>
>
>
> data (:%^&) a b = a :%^& bderiving (Show)
>
>
>
> main = do
>
>   print $ 18 :%^& (Just 99)
>
>   print $ (,) 9 10
>
>   print $ 9 , 10
>
>
>
> The last line in the code above causes a compile error.
>
> Why does infix use of the comma (tuple constructor?) function fail
> without brackets?
>

Tuples are special baked-in syntax. The parentheses are part of the tuple 
constructor(s).
It may be confusing you that you can use it prefix as well as "aroundfix".

>
>
> Thanks,
>
> Paul

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


[Haskell-cafe] Infix tuple comma query (,)

2009-04-06 Thread Paul Keir
module Main where

 

data (:%^&) a b = a :%^& bderiving (Show)

 

main = do

  print $ 18 :%^& (Just 99)

  print $ (,) 9 10

  print $ 9 , 10

 

The last line in the code above causes a compile error.

Why does infix use of the comma (tuple constructor?) function fail
without brackets?

 

Thanks,

Paul

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