1

Is there a function, or how do I write a function updateTuple, such that:

$(updateTuple 5 (0, 2, 4)) (_ -> 'a', (*2), _ -> 42) (1, 2, 3, 'b', 'c') 
  -> ('a', 2, 6, 'b', 42)

Basically the first argument of updateTuple is the length of the tuple to update, and the second is the indexes of those elements. It results in a function which takes two tuples, the first being the update functions, the second being the old tuple, and applies those update functions to the respective elements.

I looked through tuple-th but I couldn't find anything there which I could use to easily implement this.

Edit: $(updateTuple 5 [0, 2, 4]) is also ok.

Clinton
  • 22,361
  • 15
  • 67
  • 163
  • Is `$(updateTuple 5 [0, 2, 4])` syntax OK? You can't "partially apply" TH; `updateTuple` must still have a type that isn't dependent on its values. – dflemstr Aug 01 '12 at 09:29

1 Answers1

3

I kind of wanted someone else to respond, but all right. Here's the solution I made really quick:

module Tuples (updateTuple) where

import Language.Haskell.TH

updateTuple :: Int -> [Int] -> Q Exp
updateTuple len ixs = do
  ixfns <- mapM (newIxFunName . (+1)) ixs
  ixvns <- mapM newIxVarName [1..len]
  let baseVals = map VarE ixvns
      modVals = foldr applyFun baseVals $ ixs `zip` ixfns
  return . LamE [matchTuple ixfns, matchTuple ixvns] $ TupE modVals
  where
    matchTuple = TupP . map VarP
    newIxFunName = newIndexedName "fun"
    newIxVarName = newIndexedName "var"
    newIndexedName prefix = newName . (prefix ++) . show
    applyFun (ix, fn) = modifyElem ix $ AppE $ VarE fn

modifyElem :: Int -> (a -> a) -> [a] -> [a]
modifyElem 0 f (x:xs) = f x : xs
modifyElem n f (x:xs) = x : modifyElem (n - 1) f xs
modifyElem n _ [] = error $ "index " ++ show n ++ " out of bounds"

Usage example:

{-# LANGUAGE TemplateHaskell #-}
module Main where
import Tuples

main :: IO ()
main = print $ $(updateTuple 5 [0, 2, 4])
                (\ _ -> 'a', (*2), \ _ -> 42)
                (1, 2, 3, 'b', 'c')

Compilation (to show the generated code):

$ ghc -ddump-splices -fforce-recomp main.hs
[1 of 2] Compiling Tuples           ( Tuples.hs, Tuples.o )
[2 of 2] Compiling Main             ( main.hs, main.o )
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading package pretty-1.1.1.0 ... linking ... done.
Loading package array-0.4.0.0 ... linking ... done.
Loading package deepseq-1.3.0.0 ... linking ... done.
Loading package containers-0.4.2.1 ... linking ... done.
Loading package template-haskell ... linking ... done.
main.hs:6:18-40: Splicing expression
    updateTuple 5 [0, 2, 4]
  ======>
    \ (fun1_a1Cl, fun3_a1Cm, fun5_a1Cn)
      (var1_a1Co, var2_a1Cp, var3_a1Cq, var4_a1Cr, var5_a1Cs)
      -> (fun1_a1Cl var1_a1Co, var2_a1Cp, fun3_a1Cm var3_a1Cq,
          var4_a1Cr, fun5_a1Cn var5_a1Cs)
Linking main ...

Output:

$ ./main
('a',2,6,'b',42)

EDIT: Made the functions in the lambda use the same indices as the variables, makes more sense that way.

dflemstr
  • 25,947
  • 5
  • 70
  • 105
  • Just to be clear, I should add a note: the original question has no answer in pure haskell, since it requires dependent types. One has to make decision at compile type, either using type system or using macros of some sort. the latter is much easier, but the first is still possible. – permeakra Aug 01 '12 at 19:55