
Hi, I have the following data defined. data TypeCon a = ValConA a | ValConB [a] | ValConC [[a]] So I can use functions with type like (a->a->a) -> TypeCon a -> TypeCon a -> TypeCon a for all 3 value types, and I think is easier to define one single typeclass for (+), (*) etc. If I want to express the following idea (the following won't compiler): data TypeCon a = ValConA a | ValConB [ValConA a] | ValConC [ValConB a] Is this even a good idea? If so how could I proceed? The closest thing I can get to compiler is like this: data TypeCon a = ValConA a | ValConB [TypeCon a] Which is a nightmare when I try to manipulate anything in this structure. The alternative I guess is to use 3 different type constructors, data TypeConA a = ValConA a data TypeConB a = ValConB [ValConA a] data TypeConC a = ValConC [ValConB a] but then I can't use one signal typeclass for (+) etc. Am I correct? thx, //pip

I will try to help with my limited knowledge and what I believe to be going on. When you try to compile:
data TypeCon a = ValConA a | ValConB [ValConA a] | ValConC [ValConB a]
You get this: Not in scope: type constructor or class `ValConA' Not in scope: type constructor or class `ValConB' What you have here is a type constructor TypeCon and a data constructor ValConA, ValConB, ValConC. When you are constructing your different data constructors (such as ValConA) you have to give it type constructors, or substitutes like a. You can do this: data TypeCon a = ValConA a | ValConB [TypeCon a] Regards, iæfai. On 2009-11-16, at 12:33 AM, Phillip Pirrip wrote:
Hi,
I have the following data defined.
data TypeCon a = ValConA a | ValConB [a] | ValConC [[a]]
So I can use functions with type like (a->a->a) -> TypeCon a -> TypeCon a -> TypeCon a for all 3 value types, and I think is easier to define one single typeclass for (+), (*) etc.
If I want to express the following idea (the following won't compiler):
data TypeCon a = ValConA a | ValConB [ValConA a] | ValConC [ValConB a]
Is this even a good idea? If so how could I proceed? The closest thing I can get to compiler is like this:
data TypeCon a = ValConA a | ValConB [TypeCon a]
Which is a nightmare when I try to manipulate anything in this structure. The alternative I guess is to use 3 different type constructors,
data TypeConA a = ValConA a data TypeConB a = ValConB [ValConA a] data TypeConC a = ValConC [ValConB a]
but then I can't use one signal typeclass for (+) etc. Am I correct?
thx,
//pip _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Mon, Nov 16, 2009 at 12:33:51AM -0500, Phillip Pirrip wrote:
Hi,
I have the following data defined.
data TypeCon a = ValConA a | ValConB [a] | ValConC [[a]]
So I can use functions with type like (a->a->a) -> TypeCon a -> TypeCon a -> TypeCon a for all 3 value types, and I think is easier to define one single typeclass for (+), (*) etc.
If I want to express the following idea (the following won't compiler):
data TypeCon a = ValConA a | ValConB [ValConA a] | ValConC [ValConB a]
The reason this doesn't compile is that ValConA and ValConB are not types. Indeed, as their names suggest, they are value constructors. I see what you are trying to do here, but in Haskell there is no way to say 'the type of things which were constructed using the ValConB constructor', you can only say 'TypeCon a' which includes values built out of all three constructors.
data TypeCon a = ValConA a | ValConB [TypeCon a]
Which is a nightmare when I try to manipulate anything in this structure.
Right, this isn't really the same thing: this type features such fun friends as ValConB [ValConA 3, ValConA 6, ValConB [ValConB [ValConA 2], ValConA 9]] and so on.
The alternative I guess is to use 3 different type constructors,
data TypeConA a = ValConA a data TypeConB a = ValConB [ValConA a] data TypeConC a = ValConC [ValConB a]
but then I can't use one signal typeclass for (+) etc. Am I correct?
Yes, this seems like the correct alternative to me. What is so bad about having three separate (smaller) type class instances? In my opinion that would break up the code a bit and make it easier to read anyway, as opposed to a single monolithic instance for TypeCon. -Brent

On Mon, Nov 16, 2009 at 7:17 PM, Brent Yorgey
On Mon, Nov 16, 2009 at 12:33:51AM -0500, Phillip Pirrip wrote:
The alternative I guess is to use 3 different type constructors,
data TypeConA a = ValConA a data TypeConB a = ValConB [ValConA a] data TypeConC a = ValConC [ValConB a]
but then I can't use one signal typeclass for (+) etc. Am I correct?
Yes, this seems like the correct alternative to me. What is so bad
With a minor correction : data TypeConA a = ValConA a data TypeConB a = ValConB [TypeConA a] data TypeConC a = ValConC [TypeConB a]

(This e-mail is literate Haskell) Not that this is the right solution to your problems, but...
{-# LANGUAGE GADTs, EmptyDataDecls, FlexibleInstances, FlexibleContexts #-}
import Control.Applicative
This requires EmptyDataDecls:
data TypeConA data TypeConB data TypeConC
We're gonna use those empty data types as phantom types in our data type below. This requires GADTs:
data TypeCon t a where ValConA :: a -> TypeCon TypeConA a ValConB :: [TypeCon TypeConA a] -> TypeCon TypeConB a ValConC :: [TypeCon TypeConB a] -> TypeCon TypeConC a
Using the phantom types we tell the type system what kind of value we want. Now, some useful instances because we can't derive them:
instance Show a => Show (TypeCon t a) where showsPrec n x = showParen (n > 10) $ case x of ValConA a -> showString "ValConA " . showsPrec 11 a ValConB a -> showString "ValConB " . showsPrec 11 a ValConC a -> showString "ValConC " . showsPrec 11 a
instance Eq a => Eq (TypeCon t a) where (ValConA a) == (ValConA b) = (a == b) (ValConB a) == (ValConB b) = (a == b) (ValConC a) == (ValConC b) = (a == b) _ == _ = error "never here"
The 't' phantom type guarantees that we'll never reach that last definition, e.g. *Main> (ValConA True) == (ValConB []) <interactive>:1:19: Couldn't match expected type `TypeConA' against inferred type `TypeConB' Expected type: TypeCon TypeConA Bool Inferred type: TypeCon TypeConB a In the second argument of `(==)', namely `(ValConB [])' In the expression: (ValConA True) == (ValConB [])
instance Functor (TypeCon t) where fmap f (ValConA a) = ValConA (f a) fmap f (ValConB a) = ValConB (fmap (fmap f) a) fmap f (ValConC a) = ValConC (fmap (fmap f) a)
Now, if you want applicative then you'll need FlexibleInstances because we can't write 'pure :: a -> TypeCon t a'; this signature means that the user of the function may choose any 't' he wants, but we can give him only one of the 't's that appear in the constructors above.
instance Applicative (TypeCon TypeConA) where pure x = ValConA x (ValConA f) <*> (ValConA x) = ValConA (f x) _ <*> _ = error "never here"
instance Applicative (TypeCon TypeConB) where pure x = ValConB [pure x] (ValConB fs) <*> (ValConB xs) = ValConB (fmap (<*>) fs <*> xs) _ <*> _ = error "never here"
instance Applicative (TypeCon TypeConC) where pure x = ValConC [pure x] (ValConC fs) <*> (ValConC xs) = ValConC (fmap (<*>) fs <*> xs) _ <*> _ = error "never here"
Now that we have applicative we can also write, using FlexibleContexts,
liftBinOp :: Applicative (TypeCon t) => (a->b->c) -> TypeCon t a -> TypeCon t b -> TypeCon t c liftBinOp = liftA2
We need that 'Applicative' constraint because the type system doesn't know that we have already defined all possible 'Applicative' instances, so we have to live with that :). And then we can simply write
instance (Applicative (TypeCon t), Num a) => Num (TypeCon t a) where (+) = liftA2 (+) (-) = liftA2 (-) (*) = liftA2 (*) negate = fmap negate abs = fmap abs signum = fmap signum fromInteger = pure . fromInteger
Finally, *Main> let x1 = ValConB [ValConA 10, ValConA 7] *Main> let x2 = ValConB [ValConA 5, ValConA 13] *Main> x1 * x2 ValConB [ValConA 50,ValConA 130,ValConA 35,ValConA 91] HTH, -- Felipe.

Hi, Thanks everyone for their patience on my question and took the time to write back. I was thinking to re-phrase my question (to correct some typo etc), but many of you have already guessed my intent. I am trying to write a simple Matrix library, as my little learning exercise, so TypeConA : Scalar TypeConB : 1D array TypeConC : 2D array /matrix. So I would like to have one typeclass for operations like Scalar +/* Matrix etc. Felipe: you are way ahead of me (like showing me the answer before I do my exam), and I really appreciate your example code, since that is the level of understanding of Haskell I am looking forward to. I don't think I really understand the code yet, but I will give it a try and let you know. As this moment my level of understanding is basic Haskell syntax, basic Monad (going to try Monad/IArray for in-place non-destruction update) and just started to read up on Control.Applicative (and arrows) and Existential types. I have never even heard of phantom types until now. BTW, how do I generate "literate" Haskell code? I keep reading it but I still don't know how to make one (I am assuming it is more complicated then just type the code in with ">" in emacs). //pip On 2009-11-17, at 6:40 AM, Felipe Lessa wrote:
(This e-mail is literate Haskell)
Not that this is the right solution to your problems, but...
{-# LANGUAGE GADTs, EmptyDataDecls, FlexibleInstances, FlexibleContexts #-}
import Control.Applicative
This requires EmptyDataDecls:
data TypeConA data TypeConB data TypeConC
We're gonna use those empty data types as phantom types in our data type below. This requires GADTs:
data TypeCon t a where ValConA :: a -> TypeCon TypeConA a ValConB :: [TypeCon TypeConA a] -> TypeCon TypeConB a ValConC :: [TypeCon TypeConB a] -> TypeCon TypeConC a
Using the phantom types we tell the type system what kind of value we want. Now, some useful instances because we can't derive them:
instance Show a => Show (TypeCon t a) where showsPrec n x = showParen (n > 10) $ case x of ValConA a -> showString "ValConA " . showsPrec 11 a ValConB a -> showString "ValConB " . showsPrec 11 a ValConC a -> showString "ValConC " . showsPrec 11 a
instance Eq a => Eq (TypeCon t a) where (ValConA a) == (ValConA b) = (a == b) (ValConB a) == (ValConB b) = (a == b) (ValConC a) == (ValConC b) = (a == b) _ == _ = error "never here"
The 't' phantom type guarantees that we'll never reach that last definition, e.g.
*Main> (ValConA True) == (ValConB [])
<interactive>:1:19: Couldn't match expected type `TypeConA' against inferred type `TypeConB' Expected type: TypeCon TypeConA Bool Inferred type: TypeCon TypeConB a In the second argument of `(==)', namely `(ValConB [])' In the expression: (ValConA True) == (ValConB [])
instance Functor (TypeCon t) where fmap f (ValConA a) = ValConA (f a) fmap f (ValConB a) = ValConB (fmap (fmap f) a) fmap f (ValConC a) = ValConC (fmap (fmap f) a)
Now, if you want applicative then you'll need FlexibleInstances because we can't write 'pure :: a -> TypeCon t a'; this signature means that the user of the function may choose any 't' he wants, but we can give him only one of the 't's that appear in the constructors above.
instance Applicative (TypeCon TypeConA) where pure x = ValConA x (ValConA f) <*> (ValConA x) = ValConA (f x) _ <*> _ = error "never here"
instance Applicative (TypeCon TypeConB) where pure x = ValConB [pure x] (ValConB fs) <*> (ValConB xs) = ValConB (fmap (<*>) fs <*> xs) _ <*> _ = error "never here"
instance Applicative (TypeCon TypeConC) where pure x = ValConC [pure x] (ValConC fs) <*> (ValConC xs) = ValConC (fmap (<*>) fs <*> xs) _ <*> _ = error "never here"
Now that we have applicative we can also write, using FlexibleContexts,
liftBinOp :: Applicative (TypeCon t) => (a->b->c) -> TypeCon t a -> TypeCon t b -> TypeCon t c liftBinOp = liftA2
We need that 'Applicative' constraint because the type system doesn't know that we have already defined all possible 'Applicative' instances, so we have to live with that :).
And then we can simply write
instance (Applicative (TypeCon t), Num a) => Num (TypeCon t a) where (+) = liftA2 (+) (-) = liftA2 (-) (*) = liftA2 (*) negate = fmap negate abs = fmap abs signum = fmap signum fromInteger = pure . fromInteger
Finally,
*Main> let x1 = ValConB [ValConA 10, ValConA 7] *Main> let x2 = ValConB [ValConA 5, ValConA 13] *Main> x1 * x2 ValConB [ValConA 50,ValConA 130,ValConA 35,ValConA 91]
HTH,
-- Felipe.

Am Mittwoch 18 November 2009 03:46:45 schrieb Phillip Pirrip:
BTW, how do I generate "literate" Haskell code? I keep reading it but I still don't know how to make one (I am assuming it is more complicated then just type the code in with ">" in emacs).
//pip
No, it isn't. The hardest part is writing good code and comments (regardless of whether you write literate code or 'normal'). There are two ways of writing literal Haskell code, explained at http://haskell.org/onlinereport/syntax-iso.html#sect9.4 . a) 'Bird tack', start code lines with '>', write as normal (you can include -- and {- -} comments). *Separate '>'-lines from non-code lines by at least one blank line*. b) 'LaTeX' literate Haskell, code is begun by a line starting with "\begin{code}" and ended by "\end{code}". You can create really pretty stuff with that style.
participants (6)
-
Brent Yorgey
-
Daniel Fischer
-
David Virebayre
-
Felipe Lessa
-
iæfai
-
Phillip Pirrip