Deepest polymorphic functor

I was wondering if it is possible to somehow change "deep" f_map from http://okmij.org/ftp/Haskell/deepest-functor.lhs article in a such a way that it would work not only for monotypes like in the provided example: test1 = f_map (+1) [[[1::Int,2,3]]] But for polymorphic types as well (e.g. behaves like simple map) so the following line would compile as well: test1 = f_map (+1) [[[1,2,3]]] ? -- View this message in context: http://www.nabble.com/Deepest-polymorphic-functor-tp24709303p24709303.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

What would this do with
instance Num a => Num [a]
in scope?
On Tue, Jul 28, 2009 at 3:51 PM, Eduard Sergeev
I was wondering if it is possible to somehow change "deep" f_map from http://okmij.org/ftp/Haskell/deepest-functor.lhs article in a such a way that it would work not only for monotypes like in the provided example:
test1 = f_map (+1) [[[1::Int,2,3]]]
But for polymorphic types as well (e.g. behaves like simple map) so the following line would compile as well:
test1 = f_map (+1) [[[1,2,3]]]
?
-- View this message in context: http://www.nabble.com/Deepest-polymorphic-functor-tp24709303p24709303.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Ryan Ingram wrote:
What would this do with
instance Num a => Num [a]
in scope?
It should work not only for Num a anyway (like normal Functor would do) but if you could give me an example, how exactly could I use Num a here... -- View this message in context: http://www.nabble.com/Deepest-polymorphic-functor-tp24709303p24748175.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

The problem is this:
instance Num a => Num [a] where ...
test = deep_fmap (+1) [[[ 1, 2, 3 :: Int ]]]
What (+1) should be used? (+1) :: Int -> Int (+1) :: [Int] -> [Int] (+1) :: [[Int]] -> [[Int]] (+1) :: [[[Int]]] -> [[[Int]]] They could all be type-correct, so the snippet is ambiguous. Monotypes are required to avoid the ambiguity. As to why you might want an instance of this form, they are very nice for representing (possibly infinite) power series[1] of the form c0 + c1 * x + c2 * x^2 + c3 * x^3 + ... As to your other question, in my experience it seems that yes, type equality constraints can replace the awkward "TypeCast" classes of oleg-ery. -- ryan [1] Mcilroy: Functional Pearl: Power Series, Power Serious. http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.38.9450 Code here: http://journals.cambridge.org/fulltext_content/supplementary/JFP/online/jfpv...

Ryan Ingram wrote:
The problem is this:
instance Num a => Num [a] where ...
test = deep_fmap (+1) [[[ 1, 2, 3 :: Int ]]]
What (+1) should be used?
(+1) :: Int -> Int (+1) :: [Int] -> [Int] (+1) :: [[Int]] -> [[Int]] (+1) :: [[[Int]]] -> [[[Int]]]
They could all be type-correct, so the snippet is ambiguous.
But why then the following snippet doesn't cause ambiguity: deep_fmap (++"a") "b" // -> "ba" deep_fmap (++"a") ["b"] // -> ["ba"] deep_fmap (++"a") [["b"]] // -> [["ba"]] -- View this message in context: http://www.nabble.com/Deepest-polymorphic-functor-tp24709303p24751663.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

Hello Eduard, Friday, July 31, 2009, 10:26:08 AM, you wrote:
instance Num a => Num [a] where ...
But why then the following snippet doesn't cause ambiguity:
deep_fmap (++"a") "b" // -> "ba" deep_fmap (++"a") ["b"] // -> ["ba"] deep_fmap (++"a") [["b"]] // -> [["ba"]]
because it doesn't involve any instances. if you will declare class Appendable a where (++) :: a -> a -> a instance Appendable String ... instance Appendable a => Appendable [a] ... instance IsString [a] ... -- class IsString, like class Num, defines conversion rules for string constants you will get into the same trouble -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Ryan Ingram wrote:
instance Num a => Num [a] where ...
O... I see what you mean. So... no way around? e.g. no way to define deep_fmap for not grounded types? -- View this message in context: http://www.nabble.com/Deepest-polymorphic-functor-tp24709303p24752047.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

PS In regards to the original http://okmij.org/ftp/Haskell/deepest-functor.lhs Am I right that the following code from the sample: class IsCollection t coll | t -> coll instance IsCollection (m a) (m ()) instance TypeCast Atom coll => IsCollection t coll class TypeCast a b | a -> b, b->a where typeCast :: a -> b class TypeCast' t a b | t a -> b, t b -> a where typeCast' :: t->a->b class TypeCast'' t a b | t a -> b, t b -> a where typeCast'' :: t->a->b instance TypeCast' () a b => TypeCast a b where typeCast x = typeCast' () x instance TypeCast'' t a b => TypeCast' t a b where typeCast' = typeCast'' instance TypeCast'' () a a where typeCast'' _ x = x may now be reduced to: class IsCollection t coll | t -> coll instance IsCollection (m a) (m ()) instance (Atom ~ coll) => IsCollection t coll ? -- View this message in context: http://www.nabble.com/Deepest-polymorphic-functor-tp24709303p24748240.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
participants (3)
-
Bulat Ziganshin
-
Eduard Sergeev
-
Ryan Ingram