nice simple problem for someone struggling....

I'm just trying to pick up the basics....and I've managed to write this code...which remarkably works...... module Main where data SquareType = SquareConstructor Int class ShapeInterface shape where area :: shape->Int data ShapeType = forall a. ShapeInterface a => ShapeType a instance ShapeInterface SquareType where area (SquareConstructor sideLength) = sideLength * sideLength main = do putStrLn (show (area (SquareConstructor 4))) name <- getLine putStrLn "" But my next iteration was to try to parametise SquareType.... So something like data SquareType a = Num a => SquareConstructor a but of course doing this breaks everything.......sepecifically the instance declaration `SquareType' is not applied to enough type arguments Expected kind `*', but `SquareType' has kind `* -> *' In the instance declaration for `ShapeInterface SquareType' And I can't seem to get it to work.....

Nicholls, Mark wrote:
*instance* ShapeInterface SquareType *where*
area (SquareConstructor sideLength) = sideLength * sideLength
*data* SquareType a = Num a => SquareConstructor a
Now you have changed your type from SquareType to SquareType a, you need to change the instance to: instance ShapeInterface (SquareType a) where... Jules

Really....I'm sure I tried that...(as it seemed obvious) ... and it failed....but I'll have another go.... -----Original Message----- From: Jules Bean [mailto:jules@jellybean.co.uk] Sent: 21 December 2007 15:33 To: Nicholls, Mark Cc: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] nice simple problem for someone struggling.... Nicholls, Mark wrote:
*instance* ShapeInterface SquareType *where*
area (SquareConstructor sideLength) = sideLength * sideLength
*data* SquareType a = Num a => SquareConstructor a
Now you have changed your type from SquareType to SquareType a, you need to change the instance to: instance ShapeInterface (SquareType a) where... Jules

Now I have.... module Main where data SquareType numberType = Num numberType => SquareConstructor numberType data RectangleType = RectangleConstructor Int Int class ShapeInterface shape where area :: shape->Int data ShapeType = forall a. ShapeInterface a => ShapeType a instance ShapeInterface (SquareType numberType) where area (SquareConstructor sideLength) = sideLength * sideLength main = do putStrLn (show (area (SquareConstructor 4))) name <- getLine putStrLn "" but get the errors.... In the expression: sideLength * sideLength In the definition of `area': area (SquareConstructor sideLength) = sideLength * sideLength In the definition for method `area' And Couldn't match expected type `Int' against inferred type `numberType' `numberType' is a rigid type variable bound by But to be fair....I almost understand the errors....which is not bad for me.....surely "class ShapeInterface shape where area :: shape->Int" now looks dubious....I want it to be something like "class ShapeInterface shape where area :: Num numberType => shape->Int" ? but my instance declaration still complains with the errors above and I now get an error in the class declaration `numberType1' is a rigid type variable bound by.... It's slightly doing my head in....and reminds me of trying to learn C++ once....not a pleasant experience....though I did eventually succeed....to a degree. -----Original Message----- From: Jules Bean [mailto:jules@jellybean.co.uk] Sent: 21 December 2007 15:33 To: Nicholls, Mark Cc: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] nice simple problem for someone struggling.... Nicholls, Mark wrote:
*instance* ShapeInterface SquareType *where*
area (SquareConstructor sideLength) = sideLength * sideLength
*data* SquareType a = Num a => SquareConstructor a
Now you have changed your type from SquareType to SquareType a, you need to change the instance to: instance ShapeInterface (SquareType a) where... Jules

On Dec 21, 2007 11:50 AM, Nicholls, Mark
Now I have....
module Main where
data SquareType numberType = Num numberType => SquareConstructor numberType
This is a valid declaration, but I don't think it does what you want it to.
The constraint on numberType applies only to the data constructor.
That is, given an unknown value of type SquareType a for some a, we do not
have enough information to infer Num a.
For your code, you want something like:
instance (Num a) => ShapeInterface (SquareType a) where
area (SquareConstructor side) = side * side
--
Dave Menendez

Oh....
You are correct...
I thought from
"Num numberType => SquareConstructor
numberType"
We could deduce that (in English rather than get Haskell and FOL
confusion)
all values of "SquareConstructor a"....the type of a would have be be in
class Num?..
is this not correct?....if not....why not?
________________________________
From: d4ve.menendez@gmail.com [mailto:d4ve.menendez@gmail.com] On Behalf
Of David Menendez
Sent: 21 December 2007 17:05
To: Nicholls, Mark
Cc: Jules Bean; haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] nice simple problem for someone
struggling....
On Dec 21, 2007 11:50 AM, Nicholls, Mark

On Dec 21, 2007 12:08 PM, Nicholls, Mark
I thought from
"Num numberType => SquareConstructor numberType"
We could deduce that (in English rather than get Haskell and FOL confusion)
all values of "SquareConstructor a"….the type of a would have be be in class Num?..
is this not correct?....if not….why not?
That's a reasonable thing to assume. It just happens that Haskell doesn't
work that way. There's an asymmetry between constructing and
pattern-matching, and it's one that many people have complained about.
Personally, I never use class contexts in data declarations, simply because
it's too easy to get confused about what they do and do not guarantee.
--
Dave Menendez

David Menendez wrote:
That's a reasonable thing to assume. It just happens that Haskell doesn't work that way. There's an asymmetry between constructing and pattern-matching, and it's one that many people have complained about.
With GADTs turned on (-XGADTS in 6.8, -fglasgow-exts in 6.6) pattern matchings will give rise to class contexts as you would naively expect. Contexts on constructors aren't actualy haskell98, it is a bug that GHC 6.6 accepts them without any extensions being activated. Or that's my understanding, see http://hackage.haskell.org/trac/ghc/ticket/1901 Jules

On Dec 21, 2007 2:38 PM, Jules Bean
David Menendez wrote:
That's a reasonable thing to assume. It just happens that Haskell doesn't work that way. There's an asymmetry between constructing and pattern-matching, and it's one that many people have complained about.
With GADTs turned on (-XGADTS in 6.8, -fglasgow-exts in 6.6) pattern matchings will give rise to class contexts as you would naively expect.
Contexts on constructors aren't actualy haskell98, it is a bug that GHC 6.6 accepts them without any extensions being activated. Or that's my understanding, see http://hackage.haskell.org/trac/ghc/ticket/1901
I think I saw [1] and just mentally substituted [2]. In fact, until just now
I didn't know [1] was even possible. (Wasn't there some problem with class
contexts in GADTs?)
[1] data SquareType a = (Num a) => SquareConstructor a
[2] data (Num a) => SquareType a = SquareConstructor a
Okay, so pattern-matching in case [1] does guarantee Num a. In that case,
the original code didn't work because it was trying to unify Int with an
arbitrary instance of Num.
--
Dave Menendez

Let me resend the code...as it stands....
module Main where
data SquareType numberType = Num numberType => SquareConstructor
numberType
class ShapeInterface shape where
area :: Num numberType => shape->numberType
data ShapeType = forall a. ShapeInterface a => ShapeType a
instance (Num a) => ShapeInterface (SquareType a) where
area (SquareConstructor side) = side * side
and the errors are for the instance declaration.......
[1 of 1] Compiling Main ( Main.hs, C:\Documents and
Settings\nichom\Haskell\Shapes2\out/Main.o )
Main.hs:71:36:
Couldn't match expected type `numberType' against inferred type `a'
`numberType' is a rigid type variable bound by
the type signature for `area' at Main.hs:38:15
`a' is a rigid type variable bound by
the instance declaration at Main.hs:70:14
In the expression: side * side
In the definition of `area':
area (SquareConstructor side) = side * side
I'm becoming lost in errors I don't comprehend....
What bamboozles me is it seemed such a minor enhancement.
________________________________
From: d4ve.menendez@gmail.com [mailto:d4ve.menendez@gmail.com] On Behalf
Of David Menendez
Sent: 21 December 2007 17:05
To: Nicholls, Mark
Cc: Jules Bean; haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] nice simple problem for someone
struggling....
On Dec 21, 2007 11:50 AM, Nicholls, Mark

module Main where
data SquareType numberType = Num numberType => SquareConstructor numberType
class ShapeInterface shape where
area :: Num numberType => shape->numberType
data ShapeType = forall a. ShapeInterface a => ShapeType a
instance (Num a) => ShapeInterface (SquareType a) where
area (SquareConstructor side) = side * side
Awesome! That's the first e-mail I see that looks good in HTML!

On Dec 21, 2007 12:47 PM, Nicholls, Mark
Let me resend the code…as it stands….
*module* Main *where*
*data* SquareType numberType = Num numberType => SquareConstructor numberType
*class* ShapeInterface shape *where*
area :: Num numberType => shape*->*numberType
*data* ShapeType = forall a. ShapeInterface a => ShapeType a
*instance* (Num a) => ShapeInterface (SquareType a) *where*
area (SquareConstructor side) = side * side
Part of the problem is that GHC's error messages have to account for a lot
of complex typing extensions you aren't using, so they aren't clear. I'll
try to explain what's going wrong.
If you look at the function,
area (SquareConstructor side) = side * side
in isolation (that is, not as part of the class instance), it has the type
"forall a. Num a => SquareConstructor a -> a".
The function in the class declaration has type "forall a b. (ShapeInterface
a, Num b) => a -> b". The problem is that a and b are independent variables,
but the instance declaration for SquareType a requires them to be related.
I'm not sure which way you were trying to parameterize things, but here are
some possibilities:
(1) If every shape type is parameteric, then you can make ShapeInterface a
class of type constructors.
class ShapeInterface shape where
area :: Num a => shape a -> a
instance ShapeInterface SquareType where
area (SquareConstructor side) = side * side
(2) If only some shape types are parametric, you can use a multi-parameter
type class to express a relationship between the shape type and the area
type:
class ShapeInterface shape area where
area :: shape -> area
instance (Num a) => ShapeInterface (SquareType a) a where
area (SquareConstructor side) = side * side
(3) If you only need to be parameteric over some subset of numeric types,
you can use conversion functions:
class ShapeIterface shape where
area :: shape -> Rational
class (Real a) => ShapeInterface (SquareType a) where
area (SquareConstructor side) = toRational (side * side)
(Equivalently, you can replace Rational and Real with Integer and Integral.)
It may be that none of these are what you want. There are other, more
complex possibilities, but I expect they're overkill.
--
Dave Menendez

Hello, I wonder if someone could answer the following...
The short question is what does @ mean in
mulNat a b
| a <= b = mulNat' a b b
| otherwise = mulNat' b a a
where
mulNat' x@(S a) y orig
| x == one = y
| otherwise = mulNat' a (addNat orig y) orig
The long version, explaining what everything means is....
here's a definition of multiplication on natural numbers I'm reading
on a blog....
data Nat = Z | S Nat
deriving Show
one :: Nat
one = (S Z)
mulNat :: Nat -> Nat -> Nat
mulNat _ Z = Z
mulNat Z _ = Z
mulNat a b
| a <= b = mulNat' a b b
| otherwise = mulNat' b a a
where
mulNat' x@(S a) y orig
| x == one = y
| otherwise = mulNat' a (addNat orig y) orig
Haskell programmers seem to have a very irritating habit of trying to
be overly concise...which makes learnign the language extremely
hard...this example is actually relatively verbose....but anyway...
Z looks like Zero...S is the successor function...Nat are the
"Natural" numbers.....
mulNat _ Z = Z
mulNat Z _ = Z
translates to...
x * 0 = 0....fine...
0 * x = 0....fine..
mulNat a b
| a <= b = mulNat' a b b
| otherwise = mulNat' b a a
where
mulNat' x@(S a) y orig
| x == one = y
| otherwise = mulNat' a (addNat orig y) orig
is a bit more problematic...
lets take a as 3 and b as 5...
so now we have
mulNat' 3 5 5
but what does the "x@(S a)" mean? in
mulNat' x@(S a) y orig
________________________________
From: haskell-cafe-bounces@haskell.org
[mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Nicholls, Mark
Sent: 21 December 2007 17:47
To: David Menendez
Cc: Jules Bean; haskell-cafe@haskell.org
Subject: RE: [Haskell-cafe] nice simple problem for someone
struggling....
Let me resend the code...as it stands....
module Main where
data SquareType numberType = Num numberType => SquareConstructor
numberType
class ShapeInterface shape where
area :: Num numberType => shape->numberType
data ShapeType = forall a. ShapeInterface a => ShapeType a
instance (Num a) => ShapeInterface (SquareType a) where
area (SquareConstructor side) = side * side
and the errors are for the instance declaration.......
[1 of 1] Compiling Main ( Main.hs, C:\Documents and
Settings\nichom\Haskell\Shapes2\out/Main.o )
Main.hs:71:36:
Couldn't match expected type `numberType' against inferred type `a'
`numberType' is a rigid type variable bound by
the type signature for `area' at Main.hs:38:15
`a' is a rigid type variable bound by
the instance declaration at Main.hs:70:14
In the expression: side * side
In the definition of `area':
area (SquareConstructor side) = side * side
I'm becoming lost in errors I don't comprehend....
What bamboozles me is it seemed such a minor enhancement.
________________________________
From: d4ve.menendez@gmail.com [mailto:d4ve.menendez@gmail.com] On Behalf
Of David Menendez
Sent: 21 December 2007 17:05
To: Nicholls, Mark
Cc: Jules Bean; haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] nice simple problem for someone
struggling....
On Dec 21, 2007 11:50 AM, Nicholls, Mark

@ works as an aliasing primitive for the arguments of a function
f x@(Just y) = ...
using "x" in the body of f is equivalent to use "Just y". Perhaps in
this case is not really useful, but in some other cases it saves the
effort and space of retyping really long expressions. And what is even
more important, in case an error is made when choosing the pattern,
you only have to correct it in one place.
On Dec 28, 2007 12:05 PM, Nicholls, Mark
Hello, I wonder if someone could answer the following…
The short question is what does @ mean in
mulNat a b
| a <= b = mulNat' a b b
| otherwise = mulNat' b a a
where
mulNat' x@(S a) y orig
| x == one = y
| otherwise = mulNat' a (addNat orig y) orig
The long version, explaining what everything means is….
here's a definition of multiplication on natural numbers I'm reading
on a blog....
data Nat = Z | S Nat
deriving Show
one :: Nat
one = (S Z)
mulNat :: Nat -> Nat -> Nat
mulNat _ Z = Z
mulNat Z _ = Z
mulNat a b
| a <= b = mulNat' a b b
| otherwise = mulNat' b a a
where
mulNat' x@(S a) y orig
| x == one = y
| otherwise = mulNat' a (addNat orig y) orig
Haskell programmers seem to have a very irritating habit of trying to
be overly concise...which makes learnign the language extremely
hard...this example is actually relatively verbose....but anyway...
Z looks like Zero...S is the successor function...Nat are the
"Natural" numbers.....
mulNat _ Z = Z
mulNat Z _ = Z
translates to...
x * 0 = 0....fine...
0 * x = 0....fine..
mulNat a b
| a <= b = mulNat' a b b
| otherwise = mulNat' b a a
where
mulNat' x@(S a) y orig
| x == one = y
| otherwise = mulNat' a (addNat orig y) orig
is a bit more problematic...
lets take a as 3 and b as 5...
so now we have
mulNat' 3 5 5
but what does the "x@(S a)" mean? in
mulNat' x@(S a) y orig
________________________________
From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Nicholls, Mark Sent: 21 December 2007 17:47 To: David Menendez Cc: Jules Bean; haskell-cafe@haskell.org Subject: RE: [Haskell-cafe] nice simple problem for someone struggling....
Let me resend the code…as it stands….
module Main where
data SquareType numberType = Num numberType => SquareConstructor numberType
class ShapeInterface shape where
area :: Num numberType => shape->numberType
data ShapeType = forall a. ShapeInterface a => ShapeType a
instance (Num a) => ShapeInterface (SquareType a) where
area (SquareConstructor side) = side * side
and the errors are for the instance declaration…….
[1 of 1] Compiling Main ( Main.hs, C:\Documents and Settings\nichom\Haskell\Shapes2\out/Main.o )
Main.hs:71:36:
Couldn't match expected type `numberType' against inferred type `a'
`numberType' is a rigid type variable bound by
the type signature for `area' at Main.hs:38:15
`a' is a rigid type variable bound by
the instance declaration at Main.hs:70:14
In the expression: side * side
In the definition of `area':
area (SquareConstructor side) = side * side
I'm becoming lost in errors I don't comprehend….
What bamboozles me is it seemed such a minor enhancement.
________________________________
From: d4ve.menendez@gmail.com [mailto:d4ve.menendez@gmail.com] On Behalf Of David Menendez Sent: 21 December 2007 17:05 To: Nicholls, Mark Cc: Jules Bean; haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] nice simple problem for someone struggling....
On Dec 21, 2007 11:50 AM, Nicholls, Mark
wrote: Now I have....
module Main where
data SquareType numberType = Num numberType => SquareConstructor numberType
This is a valid declaration, but I don't think it does what you want it to. The constraint on numberType applies only to the data constructor.
That is, given an unknown value of type SquareType a for some a, we do not have enough information to infer Num a.
For your code, you want something like:
instance (Num a) => ShapeInterface (SquareType a) where area (SquareConstructor side) = side * side
-- Dave Menendez
<http://www.eyrie.org/~zednenem/ > _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

So in the example given...
mulNat a b
| a <= b = mulNat' a b b
| otherwise = mulNat' b a a
where
mulNat' x@(S a) y orig
| x == one = y
| otherwise = mulNat' a (addNat orig y) orig
Is equivalent to
mulNat a b
| a <= b = mulNat' a b b
| otherwise = mulNat' b a a
where
mulNat' (S a) y orig
| (S a) == one = y
| otherwise = mulNat' a (addNat orig y) orig
?
-----Original Message-----
From: Alfonso Acosta [mailto:alfonso.acosta@gmail.com]
Sent: 28 December 2007 11:20
To: Nicholls, Mark
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] what does @ mean?.....
@ works as an aliasing primitive for the arguments of a function
f x@(Just y) = ...
using "x" in the body of f is equivalent to use "Just y". Perhaps in
this case is not really useful, but in some other cases it saves the
effort and space of retyping really long expressions. And what is even
more important, in case an error is made when choosing the pattern,
you only have to correct it in one place.
On Dec 28, 2007 12:05 PM, Nicholls, Mark
Hello, I wonder if someone could answer the following...
The short question is what does @ mean in
mulNat a b
| a <= b = mulNat' a b b
| otherwise = mulNat' b a a
where
mulNat' x@(S a) y orig
| x == one = y
| otherwise = mulNat' a (addNat orig y) orig
The long version, explaining what everything means is....
here's a definition of multiplication on natural numbers I'm reading
on a blog....
data Nat = Z | S Nat
deriving Show
one :: Nat
one = (S Z)
mulNat :: Nat -> Nat -> Nat
mulNat _ Z = Z
mulNat Z _ = Z
mulNat a b
| a <= b = mulNat' a b b
| otherwise = mulNat' b a a
where
mulNat' x@(S a) y orig
| x == one = y
| otherwise = mulNat' a (addNat orig y) orig
Haskell programmers seem to have a very irritating habit of trying to
be overly concise...which makes learnign the language extremely
hard...this example is actually relatively verbose....but anyway...
Z looks like Zero...S is the successor function...Nat are the
"Natural" numbers.....
mulNat _ Z = Z
mulNat Z _ = Z
translates to...
x * 0 = 0....fine...
0 * x = 0....fine..
mulNat a b
| a <= b = mulNat' a b b
| otherwise = mulNat' b a a
where
mulNat' x@(S a) y orig
| x == one = y
| otherwise = mulNat' a (addNat orig y) orig
is a bit more problematic...
lets take a as 3 and b as 5...
so now we have
mulNat' 3 5 5
but what does the "x@(S a)" mean? in
mulNat' x@(S a) y orig
________________________________
From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Nicholls, Mark Sent: 21 December 2007 17:47 To: David Menendez Cc: Jules Bean; haskell-cafe@haskell.org Subject: RE: [Haskell-cafe] nice simple problem for someone
struggling....
Let me resend the code...as it stands....
module Main where
data SquareType numberType = Num numberType => SquareConstructor
numberType
class ShapeInterface shape where
area :: Num numberType => shape->numberType
data ShapeType = forall a. ShapeInterface a => ShapeType a
instance (Num a) => ShapeInterface (SquareType a) where
area (SquareConstructor side) = side * side
and the errors are for the instance declaration.......
[1 of 1] Compiling Main ( Main.hs, C:\Documents and Settings\nichom\Haskell\Shapes2\out/Main.o )
Main.hs:71:36:
Couldn't match expected type `numberType' against inferred type
`a'
`numberType' is a rigid type variable bound by
the type signature for `area' at Main.hs:38:15
`a' is a rigid type variable bound by
the instance declaration at Main.hs:70:14
In the expression: side * side
In the definition of `area':
area (SquareConstructor side) = side * side
I'm becoming lost in errors I don't comprehend....
What bamboozles me is it seemed such a minor enhancement.
________________________________
From: d4ve.menendez@gmail.com [mailto:d4ve.menendez@gmail.com] On
Behalf Of
David Menendez Sent: 21 December 2007 17:05 To: Nicholls, Mark Cc: Jules Bean; haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] nice simple problem for someone struggling....
On Dec 21, 2007 11:50 AM, Nicholls, Mark
wrote: Now I have....
module Main where
data SquareType numberType = Num numberType => SquareConstructor numberType
This is a valid declaration, but I don't think it does what you want it to. The constraint on numberType applies only to the data constructor.
That is, given an unknown value of type SquareType a for some a, we do not have enough information to infer Num a.
For your code, you want something like:
instance (Num a) => ShapeInterface (SquareType a) where area (SquareConstructor side) = side * side
-- Dave Menendez
<http://www.eyrie.org/~zednenem/ > _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

2007/12/28, Nicholls, Mark
So in the example given...
mulNat a b | a <= b = mulNat' a b b | otherwise = mulNat' b a a where mulNat' x@(S a) y orig | x == one = y | otherwise = mulNat' a (addNat orig y) orig
Is equivalent to
mulNat a b | a <= b = mulNat' a b b | otherwise = mulNat' b a a where mulNat' (S a) y orig | (S a) == one = y | otherwise = mulNat' a (addNat orig y) orig
?
Yes, but in the second version, it has to reconstruct (S a) before comparing it to "one" where in the first it could do the comparison directly. In this cas there may be some optimisation involved that negate this difference but in many case it can do a real performance difference. The "as-pattern" (@ means as) is both practical and performant in most cases. -- Jedaï

Lovely....thank you very much....another small step forward.
-----Original Message-----
From: Chaddaï Fouché [mailto:chaddai.fouche@gmail.com]
Sent: 28 December 2007 11:29
To: Nicholls, Mark
Cc: Alfonso Acosta; haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] what does @ mean?.....
2007/12/28, Nicholls, Mark
So in the example given...
mulNat a b | a <= b = mulNat' a b b | otherwise = mulNat' b a a where mulNat' x@(S a) y orig | x == one = y | otherwise = mulNat' a (addNat orig y) orig
Is equivalent to
mulNat a b | a <= b = mulNat' a b b | otherwise = mulNat' b a a where mulNat' (S a) y orig | (S a) == one = y | otherwise = mulNat' a (addNat orig y) orig
?
Yes, but in the second version, it has to reconstruct (S a) before comparing it to "one" where in the first it could do the comparison directly. In this cas there may be some optimisation involved that negate this difference but in many case it can do a real performance difference. The "as-pattern" (@ means as) is both practical and performant in most cases. -- Jedaï

Lets say I've got
Interface IFoo
So in the example given...
mulNat a b | a <= b = mulNat' a b b | otherwise = mulNat' b a a where mulNat' x@(S a) y orig | x == one = y | otherwise = mulNat' a (addNat orig y) orig
Is equivalent to
mulNat a b | a <= b = mulNat' a b b | otherwise = mulNat' b a a where mulNat' (S a) y orig | (S a) == one = y | otherwise = mulNat' a (addNat orig y) orig
?
Yes, but in the second version, it has to reconstruct (S a) before comparing it to "one" where in the first it could do the comparison directly. In this cas there may be some optimisation involved that negate this difference but in many case it can do a real performance difference. The "as-pattern" (@ means as) is both practical and performant in most cases. -- Jedaï _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

2007/12/28, Alfonso Acosta
@ works as an aliasing primitive for the arguments of a function
f x@(Just y) = ...
using "x" in the body of f is equivalent to use "Just y". Perhaps in this case is not really useful, but in some other cases it saves the effort and space of retyping really long expressions. And what is even more important, in case an error is made when choosing the pattern, you only have to correct it in one place.
And in plenty of case it will greatly boost your speed because you won't be reconstructing the objects against which you matched every time you want to return them unchanged. -- Jedaï

Nicholls, Mark wrote:
Hello, I wonder if someone could answer the following…
The short question is what does @ mean in
mulNat a b
| a <= b = mulNat' a b b
| otherwise = mulNat' b a a
where
mulNat' x@(S a) y orig
| x == one = y
| otherwise = mulNat' a (addNat orig y) orig
The @ means an as-pattern as defined in the Haskell 98 report section 3.17.1 http://www.haskell.org/onlinereport/exps.html#3.17.1 The 'x' binds to the whole (S a) and the 'a' binds to the parameter of the constructor 's'. There is a possible performance benefit here. Consider: zeroNothing Nothing = Nothing zeroNothing (Just n) = if n == 0 then Nothing else (Just n) versus zeroNothing Nothing = Nothing zeroNothing x@(Just n) = if n == 0 then Nothing else x The first example takes apart the (Just n) and later reconstructs (Just n). Unless the compiler is fairly clever, this will cause the new (Just n) to be a new allocation instead of reusing the input value. The second form uses an at-pattern to bind 'x' to the whole input parameter and the returned 'x' will not need to be reallocaed. -- Chris

ChrisK
zeroNothing Nothing = Nothing zeroNothing (Just n) = if n == 0 then Nothing else (Just n)
versus
zeroNothing Nothing = Nothing zeroNothing x@(Just n) = if n == 0 then Nothing else x
versus zeroNothing Nothing = Nothing zeroNothing x = let (Just n) = x in if n == 0 then Nothing else x so, @ is kind of like a let, just with its arguments flipped.

Achim Schneider wrote:
ChrisK
wrote: zeroNothing Nothing = Nothing zeroNothing (Just n) = if n == 0 then Nothing else (Just n)
versus
zeroNothing Nothing = Nothing zeroNothing x@(Just n) = if n == 0 then Nothing else x
versus
zeroNothing Nothing = Nothing zeroNothing x = let (Just n) = x in if n == 0 then Nothing else x
so, @ is kind of like a let, just with its arguments flipped.
However, if x@(Just n) fails to match, the next clause is chosen, whereas the variable pattern x matches always. Thus, the last version works only because the other possible case (Nothing) has already been handled. IOW, in the second version of zeroNothing you may swap the order of patterns, but not in the third one. Cheers Ben

Ben Franksen
Achim Schneider wrote:
ChrisK
wrote: zeroNothing Nothing = Nothing zeroNothing (Just n) = if n == 0 then Nothing else (Just n)
versus
zeroNothing Nothing = Nothing zeroNothing x@(Just n) = if n == 0 then Nothing else x
versus
zeroNothing Nothing = Nothing zeroNothing x = let (Just n) = x in if n == 0 then Nothing else x
so, @ is kind of like a let, just with its arguments flipped.
However, if x@(Just n) fails to match, the next clause is chosen, whereas the variable pattern x matches always. Thus, the last version works only because the other possible case (Nothing) has already been handled. IOW, in the second version of zeroNothing you may swap the order of patterns, but not in the third one.
Actually, I considered working it out to nothingIf :: (a -> Bool) -> Maybe a -> Maybe a nothingIf f m = m >>= (\j -> if f j then Nothing else Just j) nothingIf' :: (a -> Bool) -> Maybe a -> Maybe a nothingIf' f m = m >>= (\j -> if f j then Nothing else m) zeroNothing = nothingIf (== 0) zeroNothing' = nothingIf' (== 0) , but was too lazy. Hopefully only because it completely messes up my point. OTOH, zeroIf :: MonadPlus m => (a -> Bool) -> m a -> m a zeroIf f m = m >>= (\nz -> if f nz then mzero else m) zeroZero :: (MonadPlus m, Num a) => m a -> m a zeroZero = zeroIf (==0) makes it interesting again as you can't construct a Just value with it.

Achim Schneider
zeroIf :: MonadPlus m => (a -> Bool) -> m a -> m a zeroIf f m = m >>= (\nz -> if f nz then mzero else m)
zeroZero :: (MonadPlus m, Num a) => m a -> m a zeroZero = zeroIf (==0)
makes it interesting again as you can't construct a Just value with it.
d'oh. return nz. /me hides under a monad.

"class ShapeInterface shape where area :: shape->Int"
now looks dubious....I want it to be something like
"class ShapeInterface shape where area :: Num numberType => shape->Int" ?
Rather, I think you probably want class ShapeInterface shape where area :: Num numberType => shape -> numberType -Brent

Yes sorry....but this still fails with.... "`numberType1' is a rigid type variable bound by" ________________________________ From: Brent Yorgey [mailto:byorgey@gmail.com] Sent: 21 December 2007 17:29 To: Nicholls, Mark Cc: Jules Bean; haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] nice simple problem for someone struggling.... "class ShapeInterface shape where area :: shape->Int" now looks dubious....I want it to be something like "class ShapeInterface shape where area :: Num numberType => shape->Int" ? Rather, I think you probably want class ShapeInterface shape where area :: Num numberType => shape -> numberType -Brent
participants (10)
-
Achim Schneider
-
Alfonso Acosta
-
Ben Franksen
-
Brent Yorgey
-
Chaddaï Fouché
-
ChrisK
-
David Menendez
-
Jules Bean
-
Miguel Mitrofanov
-
Nicholls, Mark