
I have the code below that I pluged from SO. My problem is that although I sort of understand how with rewrite True and rewrite False it is suppressed that always the first element of the tuple stays as-is; I cannot find any way to apply this to the last element also. In essence there are times when I would need to change all elements of the tuple but the first and at other times I would need to change all elements except the first and the last. I don't quite understand (yet) how I could do that. Is there any way to match for a specific element eg. the third from the right or so? --Joerg {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} import Data.Typeable import GHC.Generics rewrite_ :: (Generic a, Generic b, Rewriter (Rep a), Rewrite (Rep a) ~ Rep b) => a -> b rewrite_ = to . rewrite False . from class Rewriter f where type Rewrite f :: * -> * rewrite :: Bool -> f a -> (Rewrite f) a instance Rewriter f => Rewriter (M1 i c f) where type Rewrite (M1 i c f) = M1 i c (Rewrite f) rewrite x = M1 . rewrite x . unM1 instance Typeable c => Rewriter (K1 i c) where type Rewrite (K1 i c) = K1 i String rewrite False (K1 x) | Just val <- cast x = K1 val rewrite _ _ = K1 "NIL" instance (Rewriter a, Rewriter b) => Rewriter (a :*: b) where type Rewrite (a :*: b) = Rewrite a :*: Rewrite b rewrite x (a :*: b) = rewrite x a :*: rewrite True b y0 :: (String, Int, Double) y0 = ("something", 3, 4.788) y1 :: (String, String, String, (Int, Int)) y1 = ("something else", "Hello", "NIL", (4,6)) main :: IO () main = do print (rewrite_ y0 :: (String, String, String)) print (rewrite_ y1 :: (String, String, String, String))

Hi Joerg. I must admit that I do not fully understand the big picture, i.e., why you want to do what you are trying to do. It might be possible to recommend a better solution using a library such as guarded-rewriting on Hackage then. I've tried to look up the SO question (http://stackoverflow.com/questions/13436366/manipulating-arbitrary-tuples), but it doesn't really make me understand your goal completely either. In the code you provide, which is taken from one of the answers, the Bool parameter indeed ensures that the first element of a chain of products is treated in a different way from the rest. The key to this behaviour is the line
rewrite x (a :*: b) = rewrite x a :*: rewrite True b
Here, assuming rewrite is first called with False, we ensure that the very first component of the nested product will be called with False, all others with True. Hence all but the first component will end up being rewritten. If you'd like to rewrite all but the last, you could achieve this just by writing
rewrite x (a :*: b) = rewrite True a :*: rewrite x b
instead. If you want to keep the first and the last component, you need to propagate more information than a simple Bool. One option is to create a special-purpose datatype:
data What = Both | First | Last | None deriving Eq
The type of rewrite becomes:
rewrite :: What -> f a -> (Rewrite f) a
The idea is that the What argument is initialized to Both, and in every product case, we split the current value of What to keep track if we are in the leftmost part of the product (First), the rightmost part of the product (Last), or elsewhere (None). For this, we define
splitWhat :: What -> (What, What) splitWhat Both = (First, Last) splitWhat First = (First, None) splitWhat Last = (None, Last) splitWhat None = (None, None)
The product case of rewrite is now:
rewrite x (a :*: b) = rewrite y a :*: rewrite z b where (y, z) = splitWhat x
We also need to slightly modify the K1 case of rewrite. We now want to perform the rewrite if What is anything but None:
rewrite w (K1 x) | w /= None, Just val <- cast x = K1 val rewrite _ _ = K1 "NIL"
Does this help you? (I'm attaching the full code.) Cheers, Andres -- Andres Löh, Haskell Consultant Well-Typed LLP, http://www.well-typed.com
participants (2)
-
Andres Löh
-
Joerg Fritsch