Note: One-tuples are currently understood as just the original type by Template Haskell (though this could be an undefined case which is not guaranteed to work this way?), so for example, we get
$(catTuples
1 2) = \x (y,z) -> (x,y,z)
- htuple :: Int -> TypeQ -> TypeQ
- mapTuple :: Int -> ExpQ
- mapTuple' :: Int -> ExpQ -> Q Exp
- filterTuple :: Int -> ExpQ
- filterTuple' :: Int -> ExpQ -> ExpQ
- reindexTuple :: Int -> [Int] -> Q Exp
- reverseTuple :: Int -> Q Exp
- rotateTuple :: Int -> Int -> Q Exp
- zipTuple :: Int -> Q Exp
- catTuples :: Int -> Int -> Q Exp
- uncatTuple :: Int -> Int -> Q Exp
- zipTupleWith :: Int -> ExpQ
- zipTupleWith' :: Int -> ExpQ -> ExpQ
- safeTupleFromList :: Int -> Q Exp
- tupleFromList :: Int -> Q Exp
- constTuple :: Int -> Q Exp
- proj :: Int -> Int -> ExpQ
- elemTuple :: Int -> Q Exp
- tupleToList :: Int -> Q Exp
- sumTuple :: Int -> Q Exp
- foldrTuple :: Int -> ExpQ
- foldrTuple' :: Int -> ExpQ -> ExpQ
- foldr1Tuple :: Int -> ExpQ
- foldr1Tuple' :: Int -> ExpQ -> Q Exp
- foldlTuple :: Int -> ExpQ
- foldlTuple' :: Int -> ExpQ -> ExpQ
- foldl1Tuple :: Int -> ExpQ
- foldl1Tuple' :: Int -> ExpQ -> Q Exp
- andTuple :: Int -> Q Exp
- orTuple :: Int -> Q Exp
- anyTuple :: Int -> Q Exp
- anyTuple' :: Int -> Q Exp -> Q Exp
- allTuple :: Int -> Q Exp
- allTuple' :: Int -> Q Exp -> Q Exp
- sequenceTuple :: Int -> Q Exp
- sequenceATuple :: Int -> Q Exp
Types
htuple :: Int -> TypeQ -> TypeQSource
Makes a homogenous tuple type of the given size and element type
$(htuple 2) [t| Char |] = (Char,Char)
Transformation
mapTuple' :: Int -> ExpQ -> Q ExpSource
Takes the mapping as a quoted expression. This can sometimes produce an expression that typechecks when the analogous expression using filterTuple
does not, e.g.:
$(mapTuple 2) Just ((),"foo") -- Type error $(mapTuple' 2 [| Just |]) ((),"foo") -- OK
filterTuple :: Int -> ExpQSource
Type of the generated expression:
(a -> Bool) -> (a, ..) -> [a]
filterTuple' :: Int -> ExpQ -> ExpQSource
Takes the predicate as a quoted expression. See mapTuple'
for how this can be useful.
reindexTuple :: Int -> [Int] -> Q ExpSource
reindexTuple n js
creates the function
\(x_0, ..., x_{n-1}) -> (x_{js !! 0}, x_{js !! 1}, .. x_{last js})
For example,
$(reindexTuple 3 [1,1,0,0]) ('a','b','c') == ('b','b','a','a')
Each element of js
must be nonnegative and less than n
.
rotateTuple :: Int -> Int -> Q ExpSource
rotateTuple n k
creates a function which rotates an n
-tuple rightwards by k
positions (k
may be negative or greater than n-1
).
Combination
catTuples :: Int -> Int -> Q ExpSource
Type of the generated expression:
(a1, ..) -> (b1, ..) -> (a1, .., b1, ..)
uncatTuple :: Int -> Int -> Q ExpSource
uncatTuple n m
is the inverse function of uncurry (catTuples n m)
.
ZipWith
zipTupleWith :: Int -> ExpQSource
zipTupleWith' :: Int -> ExpQ -> ExpQSource
Takes the zipping function as a quoted expression. See mapTuple'
for how this can be useful.
Construction
safeTupleFromList :: Int -> Q ExpSource
Type of the generated expression:
[a] -> Maybe (a, ..)
tupleFromList :: Int -> Q ExpSource
Type of the generated expression:
[a] -> (a, ..)
The generated function is partial.
constTuple :: Int -> Q ExpSource
Deconstruction
Generate a projection (like 'fst' and 'snd').
tupleToList :: Int -> Q ExpSource
Right folds
foldrTuple :: Int -> ExpQSource
Type of the generated expression:
(a -> r -> r) -> r -> (a, ..) -> r
foldrTuple' :: Int -> ExpQ -> ExpQSource
Takes the folding function (but not the seed element) as a quoted expression. See mapTuple'
for how this can be useful.
foldr1Tuple :: Int -> ExpQSource
Type of the generated expression:
(a -> a -> a) -> (a, ..) -> a
foldr1Tuple' :: Int -> ExpQ -> Q ExpSource
Takes the folding function as a quoted expression. See mapTuple'
for how this can be useful.
Left folds
foldlTuple :: Int -> ExpQSource
Type of the generated expression:
(r -> a -> r) -> r -> (a, ..) -> r
foldlTuple' :: Int -> ExpQ -> ExpQSource
Takes the folding function (but not the seed element) as a quoted expression. See mapTuple'
for how this can be useful.
foldl1Tuple :: Int -> ExpQSource
Type of the generated expression:
(a -> a -> a) -> (a, ..) -> a
foldl1Tuple' :: Int -> ExpQ -> Q ExpSource
Takes the folding function as a quoted expression. See mapTuple'
for how this can be useful.
Predicates
Monadic/applicative
sequenceATuple :: Int -> Q ExpSource
Like sequenceA
.