
You already have splicing for top level decls. Splicing for local decls is a whole different ball game because it brings new *binders* into scope. For example f = ...g... g = let $(foo) in ...f... Is the 'f' inside 'g' the same 'f' as the one bound at top level? Not necessarily, because $(foo) might bind f. So I can't even do dependency analysis to figure out whether f and g are mutually recursive! It gets harder if $(foo) mentions 'f'; and if the definition of 'f' has a declaration splice too. So splicing local decls introduces a new raft of questions whose answers are not obvious, and that might require some substantial structural rearrangement of GHC. In particular to the "rename and then typecheck" strategy. It's very similar to reason that we don't allow splices in patterns. Bottom line: my nose tells me this is a swamp and I'm steering clear of it for now. Simon From: Matt Morrow [mailto:moonpatio@gmail.com] Sent: 28 May 2009 00:08 To: Simon Peyton-Jones Cc: Ross Mellgren; Haskell Cafe; GHC users Subject: Re: [Haskell-cafe] Template Haskell very wordy w/r/t Decs and Types Spectacular! How difficult would it be to implement splicing in decls? I'm interested in having a go at it, and it seems like a perfect time since I can cheat off the fresh diff. In particular I'd love to be able to do stuff like this (without the current vicious hackery i'm using) (and granted, where i'm splicing is somewhat willy-nilly, but some approximation of this): ----------------------------------------------------------------------------- {-# LANGUAGE TemplateHaskell, QuasiQuotes #-} module DecTest where import HsDec import Data.List import DecTestBoot import Language.Haskell.TH.Lib import Language.Haskell.TH.Syntax import Language.Haskell.Meta.Utils bootQ :: Q [Dec] bootQ = bootQFunct primQStruct primQStruct = (''[] ,(conT ''[] `appT`) ,[|[]|] ,[|null|] ,[|undefined|] ,[|union|] ,[|undefined|] ,[|undefined|]) bootQFunct (primN :: Name ,primQ :: TypeQ -> TypeQ -- exists q. forall a. a -> q a ,emptyQ :: ExpQ -- Q a ,isEmptyQ :: ExpQ -- q a -> Bool ,insertQ :: ExpQ -- Int -> a -> q a -> q a ,mergeQ :: ExpQ -- q a -> q a -> q a ,findMinQ :: ExpQ -- q a -> Maybe (Int, a) ,deleteMinQ :: ExpQ) -- q a -> q a = do n <- newName "a" let primT = varT primN a = varT n [$dec| data BootQ $(a) = Nil | Node {-# UNPACK #-} !Int $(a) ($(primT) (BootQ $(a))) deriving(Eq,Ord) empty :: BootQ $(a) isEmpty :: BootQ $(a) -> Bool insert :: Int -> $(a) -> BootQ $(a) -> BootQ $(a) merge :: BootQ $(a) -> BootQ $(a) -> BootQ $(a) findMin :: BootQ $(a) -> Maybe (Int, $(a)) deleteMin :: BootQ $(a) -> BootQ $(a) empty = Nil isEmpty Nil = True isEmpty _ = False findMin Nil = Nothing findMin (Node n x _) = Just (n, x) insert n x q = merge (Node n x $(emptyQ)) q merge (Node n1 x1 q1) (Node n2 x2 q2) | n1 <= n2 = Node n1 x1 ($(insertQ) n2 (Node n2 x2 q2) q1) | otherwise = Node n2 x2 ($(insertQ) n1 (Node n1 x1 q1) q2) merge Nil q = q merge q Nil = q deleteMin Nil = Nil deleteMin (Node _ _ q) = case $(findMinQ) q of Nothing -> Nil Just (_, Node m y q1) -> let q2 = $(deleteMinQ) q in Node m y ($(mergeQ) q1 q2) |]