
Is there a way to get this to work? data A = Aconstructor Int data B = Bconstructor Int data AorB = A | B f :: Int -> AorB f x | even x = Aconstructor x | otherwise = Bconstructor x I get this diagnostic. Couldn't match expected type `AorB' against inferred type `A' Since AorB is A or B, why is this not permitted? If instead I write data AorB = Aconstructor Int | Bconstructor Int everything works out ok. But what if I want separate types for A and B? Thanks, * -- Russ *

Use Either A B from Data.Either:
http://www.haskell.org/ghc/docs/6.12.2/html/libraries/base-4.2.0.1/Data-Eith...
On 14 December 2010 21:09, Russ Abbott
Is there a way to get this to work?
data A = Aconstructor Int data B = Bconstructor Int data AorB = A | B f :: Int -> AorB f x | even x = Aconstructor x | otherwise = Bconstructor x
I get this diagnostic.
Couldn't match expected type `AorB' against inferred type `A'
Since AorB is A or B, why is this not permitted? If instead I write
data AorB = Aconstructor Int | Bconstructor Int
everything works out ok. But what if I want separate types for A and B? Thanks, -- Russ _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Isn't "Either" the same thing as AorB in
data AorB = Aconstructor Int | Bconstructor Int
I want two separate types A and B along with a third type which is their
Union. Is that not possible?
In my actual case, I have more than two types. So I would like a way to
take the union of an arbitrarily number of types.
data Union = A1 | A2 | ...
where each of A1, A2, ... has its own data declaration.
*
-- Russ *
On Tue, Dec 14, 2010 at 12:14 PM, Tobias Brandt
data AorB = Aconstructor Int | Bconstructor Int

On 14 December 2010 21:26, Russ Abbott
Isn't "Either" the same thing as AorB in
data AorB = Aconstructor Int | Bconstructor Int
I want two separate types A and B along with a third type which is their Union. Is that not possible?
That's exactly what either is: data A = ... data B = ... f :: Int -> Either A B
In my actual case, I have more than two types. So I would like a way to take the union of an arbitrarily number of types.
data Union = A1 | A2 | ...
where each of A1, A2, ... has its own data declaration.
You can create a new data type: data MyUnion = First A1 | Second A2 | Third A3 and use it like this: f :: Int -> MyUnion

I guess the point is that you can't put type names into the declaration of
some other type.
data A = ...
data B = ...
-- No good
data AorB = A | B
f :: Int -> AorB
f x
| even x = Aconstructor x
| otherwise = Bconstructor x
-- OK
data AorB = AType A | BType B
f :: Int -> AorB
f x
| even x = AType $ Aconstructor x
| otherwise = BType $ Bconstructor x
What's confusing is that
data AorB = A | B
compiles with error.
That raises the question of what it really means!
*-- Russ*
***
*
**
On Tue, Dec 14, 2010 at 12:35 PM, Tobias Brandt
On 14 December 2010 21:26, Russ Abbott
wrote: Isn't "Either" the same thing as AorB in
data AorB = Aconstructor Int | Bconstructor Int
I want two separate types A and B along with a third type which is their Union. Is that not possible?
That's exactly what either is:
data A = ... data B = ...
f :: Int -> Either A B
In my actual case, I have more than two types. So I would like a way to take the union of an arbitrarily number of types.
data Union = A1 | A2 | ...
where each of A1, A2, ... has its own data declaration.
You can create a new data type:
data MyUnion = First A1 | Second A2 | Third A3
and use it like this:
f :: Int -> MyUnion

On 14 December 2010 21:44, Russ Abbott
What's confusing is that
data AorB = A | B
compiles with error. That raises the question of what it really means!
You have to distinguish between type and value constructors. On the left hand side of a data declaration you have a type constructor (AorB) and possibly some type variables. On the right hand side you have value constructors followed by their arguments (types or type variables). E.g.: data TypeConstr a b c = ValueConstr1 a b | ValueConstr2 c | ValueConstr3 Int But in your example A and B were already declared as type constructors, so they can't be used again as value constructors. That's why you get an error. If you remove data A = ... and data B = ... then data AorB = A | B compiles.

Tobias you replied at the same time I was answering, you did explained what
is happening,
however, you said something which isn't right. As I mentioned before, "Type
Constructors" and
"Value Constructors" are in different scopes, and so, their names can be
used again...
if you don't believe me, give it a try with this example. I didn't even try
it, but I asure you it
will compile without any trouble:
data A = C Int
data B = D Int
data AorB = A A | B B
Greeting,
Héctor Guilarte
On Tue, Dec 14, 2010 at 4:22 PM, Tobias Brandt
On 14 December 2010 21:44, Russ Abbott
wrote: What's confusing is that
data AorB = A | B
compiles with error. That raises the question of what it really means!
You have to distinguish between type and value constructors. On the left hand side of a data declaration you have a type constructor (AorB) and possibly some type variables. On the right hand side you have value constructors followed by their arguments (types or type variables). E.g.:
data TypeConstr a b c = ValueConstr1 a b | ValueConstr2 c | ValueConstr3 Int
But in your example A and B were already declared as type constructors, so they can't be used again as value constructors. That's why you get an error. If you remove
data A = ... and data B = ...
then
data AorB = A | B
compiles.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On 14 December 2010 22:02, Hector Guilarte
Tobias you replied at the same time I was answering, you did explained what is happening, however, you said something which isn't right. As I mentioned before, "Type Constructors" and "Value Constructors" are in different scopes, and so, their names can be used again... if you don't believe me, give it a try with this example.
I believe you. As I said, I was talking crap :-)

My typo started this most recent confusion. When I wrote
data AorB = A | B
compiles with error.
That raises the question of what it really means!
I meant to say
data AorB = A | B
compiles *without *error.
That raises the question of what it really means!
*
-- Russ *
On Tue, Dec 14, 2010 at 1:04 PM, Tobias Brandt
On 14 December 2010 22:02, Hector Guilarte
wrote: Tobias you replied at the same time I was answering, you did explained what is happening, however, you said something which isn't right. As I mentioned before, "Type Constructors" and "Value Constructors" are in different scopes, and so, their names can be used again... if you don't believe me, give it a try with this example.
I believe you. As I said, I was talking crap :-)

But did you already understand what's happening?
data AorB = A | B
is pretty much like an enumeration the same as
data DayOfTheWeek = Monday | Tuesday | Wednesday | ... | Sunday
it stores no values of any type, you could even have DayOfTheWeek as a constructor in the same declaration of the data DayOfTheWeek, because they are in different scopes:
data DayOfTheWeek = Monday | Tuesday | Wednesday | ... | Sunday | DayOfTheWeek
and by no means, that A or B on the right hand side of your data AorB are referencing the data A nor the data B... In the end, you could have: data A = Aconstructor Int data B = Bconstructor Int data AorB = A A | B B f :: Int -> AorB f x | even x = A (Aconstructor x) | otherwise = B (Bconstructor x) I just added a Value to each constructor of the data AorB, which happens to be named the same as the value they store... What I'm about to do is something I haven't tried, but I don't see why it shouldn't compile:
data Try = Int Int
in data Try you have a constructor named Int, and it has a value of type
Int,
I'm trying to explain it the best I can, but I don't know if I managed to do
it
clearly, please let me know if there's something where I wasn't clear
enough.
Hector
On Tue, Dec 14, 2010 at 4:40 PM, Russ Abbott
My typo started this most recent confusion. When I wrote
data AorB = A | B
compiles with error. That raises the question of what it really means!
I meant to say
data AorB = A | B
compiles *without *error. That raises the question of what it really means!
* -- Russ *
On Tue, Dec 14, 2010 at 1:04 PM, Tobias Brandt
wrote: On 14 December 2010 22:02, Hector Guilarte
wrote: Tobias you replied at the same time I was answering, you did explained what is happening, however, you said something which isn't right. As I mentioned before, "Type Constructors" and "Value Constructors" are in different scopes, and so, their names can be used again... if you don't believe me, give it a try with this example.
I believe you. As I said, I was talking crap :-)

Thanks. I had assumed that in
data A = ...
data B = ...
data AorB = A | B
the A | B in the definition of AorB referred to the types A and B. But now I
gather that they are completely unrelated -- except for the fact that they
are spelled the same.
Thanks.
*
-- Russ *
*
*
On Tue, Dec 14, 2010 at 1:29 PM, Hector Guilarte
But did you already understand what's happening?
data AorB = A | B
is pretty much like an enumeration the same as
data DayOfTheWeek = Monday | Tuesday | Wednesday | ... | Sunday
it stores no values of any type, you could even have DayOfTheWeek as a constructor in the same declaration of the data DayOfTheWeek, because they are in different scopes:
data DayOfTheWeek = Monday | Tuesday | Wednesday | ... | Sunday | DayOfTheWeek
and by no means, that A or B on the right hand side of your data AorB are referencing the data A nor the data B...
In the end, you could have:
data A = Aconstructor Int data B = Bconstructor Int data AorB = A A | B B
f :: Int -> AorB f x | even x = A (Aconstructor x) | otherwise = B (Bconstructor x)
I just added a Value to each constructor of the data AorB, which happens to be named the same as the value they store...
What I'm about to do is something I haven't tried, but I don't see why it shouldn't compile:
data Try = Int Int
in data Try you have a constructor named Int, and it has a value of type Int,
I'm trying to explain it the best I can, but I don't know if I managed to do it clearly, please let me know if there's something where I wasn't clear enough.
Hector
On Tue, Dec 14, 2010 at 4:40 PM, Russ Abbott
wrote: My typo started this most recent confusion. When I wrote
data AorB = A | B
compiles with error. That raises the question of what it really means!
I meant to say
data AorB = A | B
compiles *without *error. That raises the question of what it really means!
* -- Russ *
On Tue, Dec 14, 2010 at 1:04 PM, Tobias Brandt
wrote:
On 14 December 2010 22:02, Hector Guilarte
wrote: Tobias you replied at the same time I was answering, you did explained what is happening, however, you said something which isn't right. As I mentioned before, "Type Constructors" and "Value Constructors" are in different scopes, and so, their names can be used again... if you don't believe me, give it a try with this example.
I believe you. As I said, I was talking crap :-)

What does "$" mean in Left $ A x. Why does not write it as "Left A x"?
For putStrLn $ "welcome", is the "$" has the same meaning as that in Left $
A x?
On Wed, Dec 15, 2010 at 4:26 AM, Russ Abbott
Isn't "Either" the same thing as AorB in
data AorB = Aconstructor Int | Bconstructor Int
I want two separate types A and B along with a third type which is their Union. Is that not possible?
In my actual case, I have more than two types. So I would like a way to take the union of an arbitrarily number of types.
data Union = A1 | A2 | ...
where each of A1, A2, ... has its own data declaration. * -- Russ *
On Tue, Dec 14, 2010 at 12:14 PM, Tobias Brandt
wrote:
data AorB = Aconstructor Int | Bconstructor Int
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On 15 Dec 2010, at 14:15, Guofeng Zhang wrote:
What does "$" mean in Left $ A x. Why does not write it as "Left A x"?
For putStrLn $ "welcome", is the "$" has the same meaning as that in Left $ A x?
It's an infix operator that does nothing but applies the thing on the left to the thing on the right. The reason it's needed is because Left A x would be parsed as (Left applied to A) applied to x, wheras what we want is Left applied to (A applied to x). This can also be done with parentheses, but is often nicer done with $. Bob

'$' has the same effect as parens around whatever's after it so 'Left
$ A x' == 'Left (A x)'. Since Haskell is left associative 'Left A x'
== '(Left A) x' which is wrong and gives me a compile error.
And yes it has the same effect as putStrLn $ "welcome".
-deech
On Wed, Dec 15, 2010 at 8:15 AM, Guofeng Zhang
What does "$" mean in Left $ A x. Why does not write it as "Left A x"? For putStrLn $ "welcome", is the "$" has the same meaning as that in Left $ A x?
On Wed, Dec 15, 2010 at 4:26 AM, Russ Abbott
wrote: Isn't "Either" the same thing as AorB in
data AorB = Aconstructor Int | Bconstructor Int
I want two separate types A and B along with a third type which is their Union. Is that not possible? In my actual case, I have more than two types. So I would like a way to take the union of an arbitrarily number of types.
data Union = A1 | A2 | ...
where each of A1, A2, ... has its own data declaration.
-- Russ
On Tue, Dec 14, 2010 at 12:14 PM, Tobias Brandt
wrote: data AorB = Aconstructor Int | Bconstructor Int
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Wednesday 15 December 2010 15:15:16, Guofeng Zhang wrote:
What does "$" mean in Left $ A x. Why does not write it as "Left A x"?
($) is used for fixity, it's a low-precedence identity for functions. You could also use parentheses for that. "Left $ A x" is equivalent to "Left (A x)" while "Left A x" would be parsed as "(Left A) x" - and therefore give a type error, since "Left A" has the type Either (Int -> A) b (assuming A is a value constructor for the type A which takes an Int argument) and not a function type, hence you can't apply it to the value x.
For putStrLn $ "welcome", is the "$" has the same meaning as that in Left $ A x?
In `putStrLn $ "welcome"', the $ is completely superfluous because you apply putStrLn to an atomic value (syntacically atomic, it's a single token), so you can say it has no meaning at all there, or it has the same meaning, implicitly adding parentheses, sort of. If you had `putStrLn $ "Welcome, " ++ name', it would again serve the same purpose, to group the tokens to yield a syntactically correct expression.

Does this help?
data A = A Int
f :: Int -> Either A B
f x
| even x = Left $ A x |
| otherwise = Right $ B x |
-deech
On Tue, Dec 14, 2010 at 2:09 PM, Russ Abbott
Is there a way to get this to work?
data A = Aconstructor Int data B = Bconstructor Int data AorB = A | B f :: Int -> AorB f x | even x = Aconstructor x | otherwise = Bconstructor x
I get this diagnostic.
Couldn't match expected type `AorB' against inferred type `A'
Since AorB is A or B, why is this not permitted? If instead I write
data AorB = Aconstructor Int | Bconstructor Int
everything works out ok. But what if I want separate types for A and B? Thanks, -- Russ _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Sorry I had a typo. Here's working code:
data A = A Int
data B = B Int
f :: Int -> Either A B
f x
| even x = Left $ A x
| otherwise = Right $ B x
-deech
On Tue, Dec 14, 2010 at 2:29 PM, aditya siram
Does this help?
data A = A Int
f :: Int -> Either A B f x | even x = Left $ A x | | otherwise = Right $ B x |
-deech
On Tue, Dec 14, 2010 at 2:09 PM, Russ Abbott
wrote: Is there a way to get this to work?
data A = Aconstructor Int data B = Bconstructor Int data AorB = A | B f :: Int -> AorB f x | even x = Aconstructor x | otherwise = Bconstructor x
I get this diagnostic.
Couldn't match expected type `AorB' against inferred type `A'
Since AorB is A or B, why is this not permitted? If instead I write
data AorB = Aconstructor Int | Bconstructor Int
everything works out ok. But what if I want separate types for A and B? Thanks, -- Russ _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Hello, Nobody has explained you why that doesn't compile... Here's the deal Suppose you have a data A which has a constructor named B and a Int
data A = B Int
now suppose you have a data C which has a constructor named A and a Int
data C = A Int
that compiles because the name of your data type is different from the constructor, that is, the names of the data types and the constructors they have are in different scopes, so for doing what you want, you would need to do:
data A = Aconstructor Int data B = Bconstructor Int data AorB = A A | B B
Where the first A is a constructor named A and the second references a data
type A,
idem for B
Hope that helps you,
Héctor Guilarte
On Tue, Dec 14, 2010 at 3:39 PM, Russ Abbott
Is there a way to get this to work?
data A = Aconstructor Int data B = Bconstructor Int data AorB = A | B
f :: Int -> AorB f x | even x = Aconstructor x | otherwise = Bconstructor x
I get this diagnostic.
Couldn't match expected type `AorB' against inferred type `A'
Since AorB is A or B, why is this not permitted?
If instead I write
data AorB = Aconstructor Int | Bconstructor Int
everything works out ok. But what if I want separate types for A and B?
Thanks, * -- Russ *
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Woah, I was talking crap. Ignore my last post.
On 14 December 2010 21:56, Hector Guilarte
data A = B Int now suppose you have a data C which has a constructor named A and a Int data C = A Int
Hello, Nobody has explained you why that doesn't compile... Here's the deal Suppose you have a data A which has a constructor named B and a Int that compiles because the name of your data type is different from the constructor, that is, the names of the data types and the constructors they have are in different scopes, so for doing what you want, you would need to do:
data A = Aconstructor Int data B = Bconstructor Int data AorB = A A | B B Where the first A is a constructor named A and the second references a data type A, idem for B Hope that helps you, Héctor Guilarte On Tue, Dec 14, 2010 at 3:39 PM, Russ Abbott
wrote: Is there a way to get this to work?
data A = Aconstructor Int data B = Bconstructor Int data AorB = A | B f :: Int -> AorB f x | even x = Aconstructor x | otherwise = Bconstructor x
I get this diagnostic.
Couldn't match expected type `AorB' against inferred type `A'
Since AorB is A or B, why is this not permitted? If instead I write
data AorB = Aconstructor Int | Bconstructor Int
everything works out ok. But what if I want separate types for A and B? Thanks, -- Russ _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Hahaha don't worry man,
Hope it helps for you too
On Tue, Dec 14, 2010 at 4:32 PM, Tobias Brandt
Woah, I was talking crap. Ignore my last post.
On 14 December 2010 21:56, Hector Guilarte
wrote: data A = B Int now suppose you have a data C which has a constructor named A and a Int data C = A Int
Hello, Nobody has explained you why that doesn't compile... Here's the deal Suppose you have a data A which has a constructor named B and a Int that compiles because the name of your data type is different from the constructor, that is, the names of the data types and the constructors they have are in different scopes, so for doing what you want, you would need to do:
data A = Aconstructor Int data B = Bconstructor Int data AorB = A A | B B Where the first A is a constructor named A and the second references a data type A, idem for B Hope that helps you, Héctor Guilarte On Tue, Dec 14, 2010 at 3:39 PM, Russ Abbott
wrote: Is there a way to get this to work?
data A = Aconstructor Int data B = Bconstructor Int data AorB = A | B f :: Int -> AorB f x | even x = Aconstructor x | otherwise = Bconstructor x
I get this diagnostic.
Couldn't match expected type `AorB' against inferred type `A'
Since AorB is A or B, why is this not permitted? If instead I write
data AorB = Aconstructor Int | Bconstructor Int
everything works out ok. But what if I want separate types for A and B? Thanks, -- Russ _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

This reminds me of an old thread started by, well me :)
http://www.haskell.org/pipermail/haskell-cafe/2010-March/074805.html (sorry
for the typos)
It is not an especially enlightening thread, but contains some nice
references.
HTH,
On 14 December 2010 20:09, Russ Abbott
Is there a way to get this to work?
data A = Aconstructor Int data B = Bconstructor Int data AorB = A | B
f :: Int -> AorB f x | even x = Aconstructor x | otherwise = Bconstructor x
I get this diagnostic.
Couldn't match expected type `AorB' against inferred type `A'
Since AorB is A or B, why is this not permitted?
If instead I write
data AorB = Aconstructor Int | Bconstructor Int
everything works out ok. But what if I want separate types for A and B?
Thanks, * -- Russ *
-- Ozgur Akgun

Thanks for the references. Glad to see this isn't an unreasonable wish.
*
-- Russ *
On Tue, Dec 14, 2010 at 2:15 PM, Ozgur Akgun
This reminds me of an old thread started by, well me :)
http://www.haskell.org/pipermail/haskell-cafe/2010-March/074805.html(sorry for the typos)
It is not an especially enlightening thread, but contains some nice references.
HTH,
On 14 December 2010 20:09, Russ Abbott
wrote: Is there a way to get this to work?
data A = Aconstructor Int data B = Bconstructor Int data AorB = A | B
f :: Int -> AorB f x | even x = Aconstructor x | otherwise = Bconstructor x
I get this diagnostic.
Couldn't match expected type `AorB' against inferred type `A'
Since AorB is A or B, why is this not permitted?
If instead I write
data AorB = Aconstructor Int | Bconstructor Int
everything works out ok. But what if I want separate types for A and B?
Thanks, * -- Russ *
-- Ozgur Akgun
participants (8)
-
aditya siram
-
Daniel Fischer
-
Guofeng Zhang
-
Hector Guilarte
-
Ozgur Akgun
-
Russ Abbott
-
Thomas Davie
-
Tobias Brandt