
Hello, I'm working on some code like the following:
class Chunkable c el | c -> el where cLength :: c -> Int cHead :: c -> Maybe el
I want to be able to map over this type, like this:
cMap :: Chunkable c' el' => (el -> el') -> c -> c'
but this isn't quite right. c' shouldn't be any instance of Chunkable, it should be the same instance except parameterized over a different type. Another approach would be something like: class (Functor c) => Chunkable c el ... except that's not right either. I think c has the wrong kind to be a Functor instance. I expect there's something very basic I'm missing. Could anyone point in the proper direction of how to do this? Can this be expressed with associated types, perhaps? Thanks, John Lato

What do you mean by parameterized over a different type?
will c have a kind of * -> * ? I don't think it has to be for what you
want to work, but the idea of "same instance" will go out the window.
Do you have a small usage example?
On Wed, Feb 11, 2009 at 11:52 AM, John Lato
Hello,
I'm working on some code like the following:
class Chunkable c el | c -> el where cLength :: c -> Int cHead :: c -> Maybe el
I want to be able to map over this type, like this:
cMap :: Chunkable c' el' => (el -> el') -> c -> c'
but this isn't quite right. c' shouldn't be any instance of Chunkable, it should be the same instance except parameterized over a different type. Another approach would be something like:
class (Functor c) => Chunkable c el ...
except that's not right either. I think c has the wrong kind to be a Functor instance.
I expect there's something very basic I'm missing. Could anyone point in the proper direction of how to do this? Can this be expressed with associated types, perhaps?
Thanks,
John Lato _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi Job,
Thanks for answering. What I'm trying to do is probably very simple,
and I think the biggest problem is that I don't fully understand kinds
yet.
Here's an example instance:
instance Chunkable [a] a where
cmap = map
--etc.
In the class I wrote, c has kind * (e.g. [a]), but then I don't see
how to write a suitable map function. For that, I would want c to
have kind * -> *. Unfortunately then I don't know to write the
others.
Would I have to do something with c having kind (* -> *) ?
class Chunkable2 c el where
cLength :: c el -> Int
cHead :: c el -> Maybe el
cMap :: (el -> el') -> c el -> c el'
Sincerely,
John
On Wed, Feb 11, 2009 at 5:12 PM, Job Vranish
What do you mean by parameterized over a different type? will c have a kind of * -> * ? I don't think it has to be for what you want to work, but the idea of "same instance" will go out the window.
Do you have a small usage example?
On Wed, Feb 11, 2009 at 11:52 AM, John Lato
wrote: Hello,
I'm working on some code like the following:
class Chunkable c el | c -> el where cLength :: c -> Int cHead :: c -> Maybe el
I want to be able to map over this type, like this:
cMap :: Chunkable c' el' => (el -> el') -> c -> c'
but this isn't quite right. c' shouldn't be any instance of Chunkable, it should be the same instance except parameterized over a different type. Another approach would be something like:
class (Functor c) => Chunkable c el ...
except that's not right either. I think c has the wrong kind to be a Functor instance.
I expect there's something very basic I'm missing. Could anyone point in the proper direction of how to do this? Can this be expressed with associated types, perhaps?
Thanks,
John Lato _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

I think what you probably want is something like this:
class Chunckable c where
cLength :: c el -> Int
cHead :: c el -> Maybe el
cMap :: (a -> b) -> c a -> c b
instance Chunckable [] where
cLength [] = 0
cLength (x:xs) = 1 + cLength xs
cHead [] = Nothing
cHead (x:xs) = Just x
cMap = map
a = [4, 7, 3, 8]
test1 = cLength a
test2 = cHead a
test3 = cMap (Just) a
The class does not actually need the second type parameter.
You can actually use all sorts of extra type variables in the type
signatures in class declarations as long as all your instances are
polymorphic across those types (not sure if that's the precise
terminology). Basically, as long as cLength, cHead and cMap do the
same thing regardless of what el is, then you don't need to have el as
a type parameter to the class.
Now if you _do_ want to have cLength, etc do something else depending
el, then things get more complicated. Maybe something like this:
class Chunckable2 c el where
cLength2 :: c el -> Int
cHead2 :: c el -> Maybe el
cMap2 :: (Chunckable2 c el') => (el -> el') -> c el -> c el'
instance Chunckable2 [] Int where
cLength2 [] = 0
cLength2 (x:xs) = 1 + cLength xs
cHead2 [] = Nothing
cHead2 (x:xs) = Just x
cMap2 = map
instance Chunckable2 [] Float where
cLength2 [] = 0
cLength2 (x:xs) = 1 + cLength xs
cHead2 [] = Nothing
cHead2 (x:xs) = Just x
cMap2 f xs = []
test4 = cMap2 (fromIntegral) (a::[Int]) :: [Float]
test5 = cMap2 (id) ([3.0, 4.0, 1.0]::[Float]) :: [Float]
Note that if you want things to work like this, functional
dependencies wont help you out (as they don't make sense in this case)
On Wed, Feb 11, 2009 at 12:34 PM, John Lato
Hi Job,
Thanks for answering. What I'm trying to do is probably very simple, and I think the biggest problem is that I don't fully understand kinds yet.
Here's an example instance:
instance Chunkable [a] a where cmap = map --etc.
In the class I wrote, c has kind * (e.g. [a]), but then I don't see how to write a suitable map function. For that, I would want c to have kind * -> *. Unfortunately then I don't know to write the others.
Would I have to do something with c having kind (* -> *) ?
class Chunkable2 c el where cLength :: c el -> Int cHead :: c el -> Maybe el cMap :: (el -> el') -> c el -> c el'
Sincerely, John
On Wed, Feb 11, 2009 at 5:12 PM, Job Vranish
wrote: What do you mean by parameterized over a different type? will c have a kind of * -> * ? I don't think it has to be for what you want to work, but the idea of "same instance" will go out the window.
Do you have a small usage example?
On Wed, Feb 11, 2009 at 11:52 AM, John Lato
wrote: Hello,
I'm working on some code like the following:
class Chunkable c el | c -> el where cLength :: c -> Int cHead :: c -> Maybe el
I want to be able to map over this type, like this:
cMap :: Chunkable c' el' => (el -> el') -> c -> c'
but this isn't quite right. c' shouldn't be any instance of Chunkable, it should be the same instance except parameterized over a different type. Another approach would be something like:
class (Functor c) => Chunkable c el ...
except that's not right either. I think c has the wrong kind to be a Functor instance.
I expect there's something very basic I'm missing. Could anyone point in the proper direction of how to do this? Can this be expressed with associated types, perhaps?
Thanks,
John Lato _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi Job, thanks for replying.
Thanks for explaining this. I never really thought about the
implications of kinds on type classes, and it's all much more clear
now.
The first version, with only one parameter, almost works, except that
some instances (e.g. uvector, storablevector) have further class
restrictions on the element types. I believe these are impossible to
express without the element parameter included in the Chunkable class.
This was a big disappointment, because otherwise it would be
possible in Haskell98.
This is also a problem with the map implementation. Since the
typeclass restriction exists for both el and el', I don't see how it's
possible to type cMap without including el' in the class. I don't
want to do that, so I guess the map function will just need to be
provided outside the class instance. It does turn out that I don't
need either fundeps or type families at least.
Thanks to everyone who replied; it really helped me clarify my
thoughts on this implementation.
Cheers,
John Lato
On Wed, Feb 11, 2009 at 8:28 PM, Job Vranish
I think what you probably want is something like this:
class Chunckable c where cLength :: c el -> Int cHead :: c el -> Maybe el cMap :: (a -> b) -> c a -> c b
instance Chunckable [] where cLength [] = 0 cLength (x:xs) = 1 + cLength xs
cHead [] = Nothing cHead (x:xs) = Just x
cMap = map
a = [4, 7, 3, 8] test1 = cLength a test2 = cHead a test3 = cMap (Just) a
The class does not actually need the second type parameter. You can actually use all sorts of extra type variables in the type signatures in class declarations as long as all your instances are polymorphic across those types (not sure if that's the precise terminology). Basically, as long as cLength, cHead and cMap do the same thing regardless of what el is, then you don't need to have el as a type parameter to the class.
Now if you _do_ want to have cLength, etc do something else depending el, then things get more complicated. Maybe something like this:
class Chunckable2 c el where cLength2 :: c el -> Int cHead2 :: c el -> Maybe el cMap2 :: (Chunckable2 c el') => (el -> el') -> c el -> c el'
instance Chunckable2 [] Int where cLength2 [] = 0 cLength2 (x:xs) = 1 + cLength xs
cHead2 [] = Nothing cHead2 (x:xs) = Just x
cMap2 = map
instance Chunckable2 [] Float where cLength2 [] = 0 cLength2 (x:xs) = 1 + cLength xs
cHead2 [] = Nothing cHead2 (x:xs) = Just x
cMap2 f xs = []
test4 = cMap2 (fromIntegral) (a::[Int]) :: [Float] test5 = cMap2 (id) ([3.0, 4.0, 1.0]::[Float]) :: [Float]
Note that if you want things to work like this, functional dependencies wont help you out (as they don't make sense in this case)
On Wed, Feb 11, 2009 at 12:34 PM, John Lato
wrote: Hi Job,
Thanks for answering. What I'm trying to do is probably very simple, and I think the biggest problem is that I don't fully understand kinds yet.
Here's an example instance:
instance Chunkable [a] a where cmap = map --etc.
In the class I wrote, c has kind * (e.g. [a]), but then I don't see how to write a suitable map function. For that, I would want c to have kind * -> *. Unfortunately then I don't know to write the others.
Would I have to do something with c having kind (* -> *) ?
class Chunkable2 c el where cLength :: c el -> Int cHead :: c el -> Maybe el cMap :: (el -> el') -> c el -> c el'
Sincerely, John
On Wed, Feb 11, 2009 at 5:12 PM, Job Vranish
wrote: What do you mean by parameterized over a different type? will c have a kind of * -> * ? I don't think it has to be for what you want to work, but the idea of "same instance" will go out the window.
Do you have a small usage example?
On Wed, Feb 11, 2009 at 11:52 AM, John Lato
wrote: Hello,
I'm working on some code like the following:
class Chunkable c el | c -> el where cLength :: c -> Int cHead :: c -> Maybe el
I want to be able to map over this type, like this:
cMap :: Chunkable c' el' => (el -> el') -> c -> c'
but this isn't quite right. c' shouldn't be any instance of Chunkable, it should be the same instance except parameterized over a different type. Another approach would be something like:
class (Functor c) => Chunkable c el ...
except that's not right either. I think c has the wrong kind to be a Functor instance.
I expect there's something very basic I'm missing. Could anyone point in the proper direction of how to do this? Can this be expressed with associated types, perhaps?
Thanks,
John Lato _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

One clarification. That is, I could write map with the cNull/cCons
implementation already suggested, but I couldn't do:
instance Chunkable Data.StorableVector.Vector el where
...
cMap = Data.StorableVector.map
which is what I really want.
However, I just realized that I should be able to use the cNull cCons
implementation with a rewrite rule for this case, so I think I'm happy
now.
John
On Thu, Feb 12, 2009 at 11:08 PM, John Lato
Hi Job, thanks for replying.
Thanks for explaining this. I never really thought about the implications of kinds on type classes, and it's all much more clear now.
The first version, with only one parameter, almost works, except that some instances (e.g. uvector, storablevector) have further class restrictions on the element types. I believe these are impossible to express without the element parameter included in the Chunkable class. This was a big disappointment, because otherwise it would be possible in Haskell98.
This is also a problem with the map implementation. Since the typeclass restriction exists for both el and el', I don't see how it's possible to type cMap without including el' in the class. I don't want to do that, so I guess the map function will just need to be provided outside the class instance. It does turn out that I don't need either fundeps or type families at least.
Thanks to everyone who replied; it really helped me clarify my thoughts on this implementation.
Cheers, John Lato
On Wed, Feb 11, 2009 at 8:28 PM, Job Vranish
wrote: I think what you probably want is something like this:
class Chunckable c where cLength :: c el -> Int cHead :: c el -> Maybe el cMap :: (a -> b) -> c a -> c b
instance Chunckable [] where cLength [] = 0 cLength (x:xs) = 1 + cLength xs
cHead [] = Nothing cHead (x:xs) = Just x
cMap = map
a = [4, 7, 3, 8] test1 = cLength a test2 = cHead a test3 = cMap (Just) a
The class does not actually need the second type parameter. You can actually use all sorts of extra type variables in the type signatures in class declarations as long as all your instances are polymorphic across those types (not sure if that's the precise terminology). Basically, as long as cLength, cHead and cMap do the same thing regardless of what el is, then you don't need to have el as a type parameter to the class.
Now if you _do_ want to have cLength, etc do something else depending el, then things get more complicated. Maybe something like this:
class Chunckable2 c el where cLength2 :: c el -> Int cHead2 :: c el -> Maybe el cMap2 :: (Chunckable2 c el') => (el -> el') -> c el -> c el'
instance Chunckable2 [] Int where cLength2 [] = 0 cLength2 (x:xs) = 1 + cLength xs
cHead2 [] = Nothing cHead2 (x:xs) = Just x
cMap2 = map
instance Chunckable2 [] Float where cLength2 [] = 0 cLength2 (x:xs) = 1 + cLength xs
cHead2 [] = Nothing cHead2 (x:xs) = Just x
cMap2 f xs = []
test4 = cMap2 (fromIntegral) (a::[Int]) :: [Float] test5 = cMap2 (id) ([3.0, 4.0, 1.0]::[Float]) :: [Float]
Note that if you want things to work like this, functional dependencies wont help you out (as they don't make sense in this case)
On Wed, Feb 11, 2009 at 12:34 PM, John Lato
wrote: Hi Job,
Thanks for answering. What I'm trying to do is probably very simple, and I think the biggest problem is that I don't fully understand kinds yet.
Here's an example instance:
instance Chunkable [a] a where cmap = map --etc.
In the class I wrote, c has kind * (e.g. [a]), but then I don't see how to write a suitable map function. For that, I would want c to have kind * -> *. Unfortunately then I don't know to write the others.
Would I have to do something with c having kind (* -> *) ?
class Chunkable2 c el where cLength :: c el -> Int cHead :: c el -> Maybe el cMap :: (el -> el') -> c el -> c el'
Sincerely, John
On Wed, Feb 11, 2009 at 5:12 PM, Job Vranish
wrote: What do you mean by parameterized over a different type? will c have a kind of * -> * ? I don't think it has to be for what you want to work, but the idea of "same instance" will go out the window.
Do you have a small usage example?
On Wed, Feb 11, 2009 at 11:52 AM, John Lato
wrote: Hello,
I'm working on some code like the following:
class Chunkable c el | c -> el where cLength :: c -> Int cHead :: c -> Maybe el
I want to be able to map over this type, like this:
cMap :: Chunkable c' el' => (el -> el') -> c -> c'
but this isn't quite right. c' shouldn't be any instance of Chunkable, it should be the same instance except parameterized over a different type. Another approach would be something like:
class (Functor c) => Chunkable c el ...
except that's not right either. I think c has the wrong kind to be a Functor instance.
I expect there's something very basic I'm missing. Could anyone point in the proper direction of how to do this? Can this be expressed with associated types, perhaps?
Thanks,
John Lato _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

You can do this with another type class.
class (Chunkable c1 el1, Chunkable c2 el2) => ChunkMap c1 el1 c2 el2 where
cMap :: (el1 -> el2) -> c1 -> c2
instance ChunkMap [a] a [b] b where cMap = map
If you want to assert that c1 and c2 are really related, you can add
functional dependencies to specify the relation:
class ... | c1 el2 -> c2, c2 el1 -> c1 where ...
Combined with the dependencies in the superclass, this says that if we
have c1 and el2 we can determine c2 and el1, and vice versa.
Also, if "chunkable" has a notion of "cons", "empty", and "fold", you
can write a generic map between any two chunkable instances:
genericCMap :: (Chunkable c1 el1, Chunkable c2 el2) => (el1 -> el2) -> c1 -> c2
genericCMap f = cFold (\x xs -> cCons (f x) xs) cEmpty
-- ryan
P.S. Check out Data.Traversable.
On Wed, Feb 11, 2009 at 8:52 AM, John Lato
Hello,
I'm working on some code like the following:
class Chunkable c el | c -> el where cLength :: c -> Int cHead :: c -> Maybe el
I want to be able to map over this type, like this:
cMap :: Chunkable c' el' => (el -> el') -> c -> c'
but this isn't quite right. c' shouldn't be any instance of Chunkable, it should be the same instance except parameterized over a different type. Another approach would be something like:
class (Functor c) => Chunkable c el ...
except that's not right either. I think c has the wrong kind to be a Functor instance.
I expect there's something very basic I'm missing. Could anyone point in the proper direction of how to do this? Can this be expressed with associated types, perhaps?
Thanks,
John Lato _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (3)
-
Job Vranish
-
John Lato
-
Ryan Ingram