[Haskell-cafe] Can this be made to fuse?

David Feuer david.feuer at gmail.com
Sun Sep 11 23:05:32 UTC 2022


The template-haskell package has functions `tupE` and `tupP` for
building tuple expressions and patterns, respectively, but nothing
really similar for building tuple types. I came up with the version
below the other day:

-- | Given a list of types, produce the type of a tuple of
-- those types. This is analogous to 'tupE' and 'tupP'.
--
-- @
-- tupT [[t|Int|], [t|Char|], [t|Bool]] = [t| (Int, Char, Bool) |]
-- @
tupT :: [Q Type] -> Q Type
tupT ts = n `seq` res
  where
    -- We build the expression with a thunk inside that will be filled in with
    -- the length of the list once that's been determined. This works
    -- efficiently (in one pass) because TH.Type is rather lazy.
    (res, n) = foldl' (\(acc, !k) ty -> ([t| $acc $ty |], k + 1))
                      (tupleT n, 0)
                      ts

I strongly suspect this is quite fast enough in practice, but it's a
bit annoying that it won't participate in list fusion; tupT (map f xs)
will (lazily) generate an intermediate list. I wasn't able to convince
GHC to fuse it, short of a custom rewrite rule or two (tupT (build f)
= ..., tupT (augment f r = ...). Does anyone know if it's possible?


More information about the Haskell-Cafe mailing list