
Scary words warning: Polynomial, Functor, Bifunctor, unsafeCoerce# Folks A peculiar query for folks who know more about the internals of Haskell compilers than I do. I attach the full code with all the bits and pieces, but let me pull out the essentials in order to state the problem. I've been mucking around with polynomial types in one parameter
newtype Id x = Id x -- element newtype K1 a x = K1 a -- constant data ((Sum1 p q)) x = L1 (p x) | R1 (q x) -- choice data ((Prod1 p q)) x = P1 (p x) (q x) -- pairing
all of which give unremarkable instances of Functor < class Functor p where < fmap :: (s -> t) -> p s -> p t
instance Functor Id instance Functor (K1 a) instance (Functor p, Functor q) => Functor (Sum1 p q) instance (Functor p, Functor q) => Functor (Prod1 p q)
I've also been mucking around with polynomial types in two parameters
newtype Fst x y = Fst x newtype Snd x y = Snd y newtype K2 a x y = K2 a data ((Sum2 p q)) x y = L2 (p x y) | R2 (q x y) data ((Prod2 p q)) x y = P2 (p x y) (q x y)
which give unremarkable bifunctors, doing two maps at once
class Bifunctor p where bimap :: (s1 -> t1) -> (s2 -> t2) -> p s1 s2 -> p t1 t2
instance Bifunctor Fst where bimap f g (Fst x) = Fst (f x)
instance Bifunctor Snd where bimap f g (Snd y) = Snd (g y)
instance Bifunctor (K2 a) instance (Bifunctor p, Bifunctor q) => Bifunctor (Sum2 p q) instance (Bifunctor p, Bifunctor q) => Bifunctor (Prod2 p q)
Now, I'm interested in collapsing the diagonal. What? Er, this:
class (Bifunctor b, Functor f) => Diag b f | b -> f where diag :: b x x -> f x gaid :: f x -> b x x
If the two parameters to a bifunctor are instantiated with the same thing, we should be able to exchange with the functorial representation. I'll just do one way.
instance Diag Fst Id where diag (Fst x) = Id x
instance Diag Snd Id where diag (Snd x) = Id x
instance Diag (K2 a) (K1 a) where diag (K2 a) = K1 a
instance (Diag pb pf, Diag qb qf) => Diag (Sum2 pb qb) (Sum1 pf qf) where diag (L2 p) = L1 (diag p) diag (R2 q) = R1 (diag q)
instance (Diag pb pf, Diag qb qf) => Diag (Prod2 pb qb) (Prod1 pf qf) where diag (P2 p q) = P1 (diag p) (diag q)
That looks like a whole lot of doing very little. So, can I (in practice, in this or that compiler) get away with...
dodgy :: Diag b f => b x x -> f x dodgy = unsafeCoerce#
ygdod :: Diag b f => f x -> b x x ygdod = unsafeCoerce#
...dodgy for diag and ygdod for giad? Minimal nontrivial experiments in ghc give grounds for cautious optimism, but I'd be delighted to hear from better informed sources. Cheers Conor ------------------