[Haskell-cafe] RE: [Haskell] boilerplate boilerplate

Claus Reinke claus.reinke at talk21.com
Mon Jun 4 07:43:18 EDT 2007


>> I suppose a deriveAll command from template haskell would work.  Is that
>> really possible?
> 
> Asking people who have more knowledge of template haskell, I'm still not sure.
> 
> What it would really rely on is:
> 
> getDataDeclarationsInCurrentModule :: Q [Dec]
> 
> Whether that can be done or not is still not something I'm sure on.

it's been a while since i played with TH, but the "stage fright" (staging restrictions)
are likely to get in the way. you could do something like the two-level approach
below, though, giving you:

    *Main> ds
    "[DataD [] Hi [] [NormalC Hi [(NotStrict,ConT GHC.Base.String)]] []]"
    *Main> ds'
    "[DataD [] Hi [] [NormalC Hi [(NotStrict,ConT GHC.Base.String)]] [GHC.Show.Show]]"
    *Main> :i Hi
    data Hi = Hi String
            -- Defined at C:/Documents and Settings/cr3/Desktop/TH.hs:12:2
    instance Show Hi
      -- Defined at C:/Documents and Settings/cr3/Desktop/TH.hs:12:2

but do you want to go down that route? what is the reason for avoiding simple
preprocessing using sed or Data.Derive or just Haskell? it isn't as if your clients
would have to know about where those generated modules came from, is it?
all they would see would be another Haskell module to compile. all you would
see would be an extra line in the build script for creating a source distribution.

claus

-----------------------------------------------------
{-# OPTIONS_GHC -fth #-}
module THI where

import Language.Haskell.TH
import Language.Haskell.TH.Syntax

rds = [d| 
  data Hi = Hi String 
  |]

add c (DataD ctxt n ns cs ds) = DataD ctxt n ns cs (c:ds)
add c d = d

rds' = rds >>= return . map (add ''Show)
-----------------------------------------------------
{-# OPTIONS_GHC -fth #-}
module Main where

import Language.Haskell.TH
import Language.Haskell.TH.Syntax
import THI

ds = $(rds >>= lift . show)

ds' = $(rds' >>= lift . show)

$(rds')



More information about the Haskell-Cafe mailing list