
Hi! I have a syntax tree defined like this:
data A a = A Int Int (B a)
data B a = B String String (C a)
data C a = C Int Int (D a)
and so on, all the data are parametrized with a type variable. This variable is actually used as a field in the very end of a hierarchy:
data D a = D Int a
Now I have to write a function which would copy (A Int) to (A String). Is it possible to do so using TH/syb without writing copyA (A i1 i2 b) = A i1 i2 (copyB b) copyB = ... copyC = ... .. copyD (D i a) = D i (show a) ? Could you provide me with a hint? Thanks, Sergey

You could add {-# LANGUAGE DeriveFunctor #-}, and then add 'deriving
Functor' to all your data types (or you could of course manually
define your functor instances). Then what you want is just 'fmap
show'.
Erik
On Tue, Oct 2, 2012 at 9:55 AM, Sergey Mironov
Hi! I have a syntax tree defined like this:
data A a = A Int Int (B a)
data B a = B String String (C a)
data C a = C Int Int (D a)
and so on, all the data are parametrized with a type variable. This variable is actually used as a field in the very end of a hierarchy:
data D a = D Int a
Now I have to write a function which would copy (A Int) to (A String). Is it possible to do so using TH/syb without writing
copyA (A i1 i2 b) = A i1 i2 (copyB b) copyB = ... copyC = ... .. copyD (D i a) = D i (show a) ?
Could you provide me with a hint?
Thanks, Sergey
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Yes, thats good solution. Let me complicate things a bit. Lets define last data, D, in a different way:
data A a = A Int Int (B a) data B a = B String String (C a) data C a = C Int Int (D a)
data D a = D Int (F a)
where F is a type function
type family F t data Stage1 data Stage2 type instance F Stage1 = Int type instance F Stage2 = String
This time D is not a functor, because 'a' can accept only either
Stage1 or Stage2. And what I need is to quickly define copy :: A
Stage1 -> A Stage2
is it possible without writing boilerplate?
2012/10/2 Erik Hesselink
You could add {-# LANGUAGE DeriveFunctor #-}, and then add 'deriving Functor' to all your data types (or you could of course manually define your functor instances). Then what you want is just 'fmap show'.
Erik
On Tue, Oct 2, 2012 at 9:55 AM, Sergey Mironov
wrote: Hi! I have a syntax tree defined like this:
data A a = A Int Int (B a)
data B a = B String String (C a)
data C a = C Int Int (D a)
and so on, all the data are parametrized with a type variable. This variable is actually used as a field in the very end of a hierarchy:
data D a = D Int a
Now I have to write a function which would copy (A Int) to (A String). Is it possible to do so using TH/syb without writing
copyA (A i1 i2 b) = A i1 i2 (copyB b) copyB = ... copyC = ... .. copyD (D i a) = D i (show a) ?
Could you provide me with a hint?
Thanks, Sergey
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (2)
-
Erik Hesselink
-
Sergey Mironov