Spectacular!<br><br>How difficult would it be to implement splicing in decls? I&#39;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&#39;d love to be able to do stuff like this (without the current vicious hackery i&#39;m using) (and granted, where i&#39;m splicing is somewhat willy-nilly, but some approximation of this):<br>
<br>-----------------------------------------------------------------------------<br><br>{-# LANGUAGE TemplateHaskell, QuasiQuotes #-}<br>module DecTest where<br>import HsDec<br>import Data.List<br>import DecTestBoot<br>import Language.Haskell.TH.Lib<br>
import Language.Haskell.TH.Syntax<br>import Language.Haskell.Meta.Utils<br><br>bootQ :: Q [Dec]<br>bootQ = bootQFunct<br>          primQStruct<br><br>primQStruct = (&#39;&#39;[]<br>              ,(conT &#39;&#39;[] `appT`)<br>
              ,[|[]|]<br>              ,[|null|]<br>              ,[|undefined|]<br>              ,[|union|]<br>              ,[|undefined|]<br>              ,[|undefined|])<br><br>bootQFunct<br>  (primN      :: Name<br>  ,primQ      :: TypeQ<br>
              -&gt; TypeQ  -- exists q. forall a. a -&gt; q a<br>  ,emptyQ     :: ExpQ   -- Q a<br>  ,isEmptyQ   :: ExpQ   -- q a -&gt; Bool<br>  ,insertQ    :: ExpQ   -- Int -&gt; a -&gt; q a -&gt; q a<br>  ,mergeQ     :: ExpQ   -- q a -&gt; q a -&gt; q a<br>
  ,findMinQ   :: ExpQ   -- q a -&gt; Maybe (Int, a)<br>  ,deleteMinQ :: ExpQ)  -- q a -&gt; q a<br><br>  = do  n &lt;- newName &quot;a&quot;<br>        let primT = varT primN<br>            a = varT n<br><br>        [$dec|<br>
          data BootQ $(a)<br>            = Nil<br>            | Node {-# UNPACK #-} !Int $(a) ($(primT) (BootQ $(a)))<br>            deriving(Eq,Ord)<br><br>          empty     :: BootQ $(a)<br>          isEmpty   :: BootQ $(a) -&gt; Bool<br>
          insert    :: Int -&gt; $(a) -&gt; BootQ $(a) -&gt; BootQ $(a)<br>          merge     :: BootQ $(a) -&gt; BootQ $(a) -&gt; BootQ $(a)<br>          findMin   :: BootQ $(a) -&gt; Maybe (Int, $(a))<br>          deleteMin :: BootQ $(a) -&gt; BootQ $(a)<br>
<br>          empty = Nil<br>          isEmpty Nil = True<br>          isEmpty   _ = False<br>          findMin  Nil = Nothing<br>          findMin (Node n x _) = Just (n, x)<br>          insert n x q = merge (Node n x $(emptyQ)) q<br>
          merge (Node n1 x1 q1)<br>                (Node n2 x2 q2)<br>            | n1 &lt;= n2  = Node n1 x1 ($(insertQ) n2 (Node n2 x2 q2) q1)<br>            | otherwise = Node n2 x2 ($(insertQ) n1 (Node n1 x1 q1) q2)<br>
          merge Nil q  = q<br>          merge q  Nil = q<br>          deleteMin  Nil = Nil<br>          deleteMin (Node _ _ q)<br>            = case $(findMinQ) q of<br>                Nothing -&gt; Nil<br>                Just (_, Node m y q1)<br>
                  -&gt; let q2 = $(deleteMinQ) q<br>                      in Node m y ($(mergeQ) q1 q2)<br>            |]<br><br>{-<br>-- FORGOT TO PUT AN (Eq a) CXT, but oh well<br>ghci&gt; ppDoc `fmap` bootQ<br>data BootQ a_0_0 = Nil | Node !Int a_0_0 ([] (BootQ a_0_0))<br>
    deriving (Eq, Ord)<br>empty :: forall a_0_1 . BootQ a_0_1<br>isEmpty :: forall a_0_2 . BootQ a_0_2 -&gt; Bool<br>insert :: forall a_0_3 . Int -&gt; a_0_3 -&gt; BootQ a_0_3 -&gt; BootQ a_0_3<br>merge :: forall a_0_4 . BootQ a_0_4 -&gt; BootQ a_0_4 -&gt; BootQ a_0_4<br>
findMin :: forall a_0_5 . BootQ a_0_5 -&gt; Maybe ((Int, a_0_5))<br>deleteMin :: forall a_0_6 . BootQ a_0_6 -&gt; BootQ a_0_6<br>empty = Nil<br>isEmpty (Nil) = True<br>isEmpty _ = False<br>findMin (Nil) = Nothing<br>findMin (Node n_7 x_8 _) = Just (n_7, x_8)<br>
insert n_9 x_10 q_11 = merge (Node n_9 x_10 []) q_11<br>merge (Node n1_12 x1_13 q1_14) (Node n2_15<br>                                     x2_16<br>                                     q2_17) | n1_12 &lt;= n2_15 = Node n1_12 x1_13 (undefined n2_15 (Node n2_15 x2_16 q2_17) q1_14)<br>
                                            | otherwise = Node n2_15 x2_16 (undefined n1_12 (Node n1_12 x1_13 q1_14) q2_17)<br>merge (Nil) q_18 = q_18<br>merge q_19 (Nil) = q_19<br>deleteMin (Nil) = Nil<br>deleteMin (Node _ _ q_20) = case undefined q_20 of<br>
                                Nothing -&gt; Nil<br>                                Just (_, Node m_21 y_22 q1_23) -&gt; let q2_24 = undefined q_20<br>                                                                   in Node m_21 y_22 (union q1_23 q2_24)<br>
ghci&gt;<br>-}<br><br>-----------------------------------------------------------------------------<br><br>Thanks,<br>Matt<br><br><br><br><div class="gmail_quote">On Wed, May 27, 2009 at 2:38 PM, Simon Peyton-Jones <span dir="ltr">&lt;<a href="mailto:simonpj@microsoft.com">simonpj@microsoft.com</a>&gt;</span> wrote:<br>
<blockquote class="gmail_quote" style="border-left: 1px solid rgb(204, 204, 204); margin: 0pt 0pt 0pt 0.8ex; padding-left: 1ex;">Folks<br>
<br>
Quite a few people have asked for splices in Template Haskell *types*, and I have finally gotten around to implementing them.  So now you can write things like<br>
<br>
        instance Binary $(blah blah) where ...<br>
or      f :: $(wubble bubble) -&gt; Int<br>
<br>
as requested, for example, in the message below.  Give it a whirl.  You need the HEAD; in a day or two you should find binary snapshots if you don&#39;t want to build from source.<br>
<br>
        Simon<br>
<br>
PS: Note that you (still) cannot write a splice in a *binding* position. Thus you can&#39;t write<br>
        f $(blah blah) = e<br>
or<br>
        data T $(blah blah) = MkT Int<br>
<br>
I don&#39;t intend to change this; see the commentary at <a href="http://hackage.haskell.org/trac/ghc/ticket/1476" target="_blank">http://hackage.haskell.org/trac/ghc/ticket/1476</a><br>
<br>
| -----Original Message-----<br>
| From: <a href="mailto:haskell-cafe-bounces@haskell.org">haskell-cafe-bounces@haskell.org</a> [mailto:<a href="mailto:haskell-cafe-bounces@haskell.org">haskell-cafe-bounces@haskell.org</a>] On<br>
| Behalf Of Ross Mellgren<br>
| Sent: 25 January 2009 19:55<br>
| To: Haskell Cafe<br>
| Subject: [Haskell-cafe] Template Haskell very wordy w/r/t Decs and Types<br>
|<br>
| Hi all,<br>
|<br>
| I&#39;m writing a small module that exposes a template haskell splice that<br>
| takes a (very simplified) C struct definition and builds:<br>
|<br>
|   - A data type definition,<br>
|   - an instance for Data.Binary.Binary,<br>
|   - and optionally a pretty print function for it<br>
|<br>
| However, it seems to do this I have to write a bunch of really ugly<br>
| code that builds up the TH data structures &quot;by hand&quot; because quoting<br>
| only works with splices for expressions, or so it seems.<br>
|<br>
| For example, to generate the binary instance I have this code:<br>
|<br>
| import qualified <a href="http://Language.Haskell.TH" target="_blank">Language.Haskell.TH</a> as TH<br>
|<br>
| -- tyname is the name of the data type I&#39;ve already created, as a<br>
| TH.Name<br>
| -- tempnames is a list of temporary variable names that are used in<br>
| lambda patterns<br>
| -- fields is a list of tuples describing each field<br>
| -- makeGetExp recursively builds a monadic computation consisting<br>
| mostly of Binary.getWord32be &gt;&gt;= \ tempvar -&gt; ...<br>
|<br>
|      binaryInstDec &lt;- liftM (TH.InstanceD [] (TH.AppT (TH.ConT $<br>
| TH.mkName &quot;Data.Binary.Binary&quot;) (TH.ConT tyname)))<br>
|                             [d| get = $(makeGetExp (reverse $ zip<br>
| fields tempnames) returnExp)<br>
|                                 put = undefined |]<br>
|<br>
| I&#39;d really rather write:<br>
|<br>
|      binaryInstDec &lt;- [d|<br>
|          instance Binary.Binary $(tyname) where<br>
|              get = $(makeGetExp (reverse $ zip fields tempnames)<br>
| returnExp)<br>
|              put = undefined |]<br>
|<br>
| But GHC gives me a syntax error on the tyname splice. The docs seem to<br>
| indicate this is the way it is -- that splices in type locations is<br>
| plain not implemented.<br>
|<br>
| My question is whether or not this is just the way it is, and people<br>
| writing TH declaration splices tend to have to start manually<br>
| assembling a bunch of it, or is there some trick I&#39;ve missed? Perhaps<br>
| even better are there some tricks that people tend to use to make this<br>
| less painful?<br>
|<br>
| I did try using some of the lowercased monadic constructors in<br>
| Language.Haskell.TH.Lib but I didn&#39;t seem to get anything more succint<br>
| out of it.<br>
_______________________________________________<br>
Haskell-Cafe mailing list<br>
<a href="mailto:Haskell-Cafe@haskell.org">Haskell-Cafe@haskell.org</a><br>
<a href="http://www.haskell.org/mailman/listinfo/haskell-cafe" target="_blank">http://www.haskell.org/mailman/listinfo/haskell-cafe</a><br>
</blockquote></div><br>