[Template-haskell] Records and generating splices

Rene de Visser rene_de_visser at hotmail.com
Fri Jul 8 08:40:18 EDT 2005


Hello,

In the following code I wish to generate the invidual accessors, i.e. the 
add_rel1, add_rel2, etc.

I have tried using

test = [| add_rel1 value = modify (\db -> db{ rel1 = Set.insert value (rel1 
db)}) |]

with some splicing, but it does not seem possible to splice in the rel1 
before the '='.
Also how do I splice in the add_rel1?

According to the documentation it is only possible to splice in complete 
expressions. This seems quite limiting. Does this mean you always have to 
construct the expressions by hand?

The library documention seems very thin. Its hard to tell how to create a 
record accessor and setter from the haddock documentation.

Note that I have no experience with template haskell.

It would also be nice to generate the type declaration, but I am finding 
this even more difficult.

Can any one provide some example code to do this.

Rene.


{-# OPTIONS -fglasgow-exts #-}
module DataBase where

import Control.Monad.State
import qualified Data.Set as Set
-- Does this really need to be extensible???
-- Entries need to be based on sets, or something similar...
data SmallDB = SmallDB { rel1 :: Set.Set String
                       , rel2 :: Set.Set Integer } deriving Show

emptyDB = SmallDB Set.empty Set.empty

add_rel1 :: (MonadState SmallDB m) => String -> m ()
add_rel1 value = modify (\db -> db{ rel1 = Set.insert value (rel1 db)})

add_rel2 :: (MonadState SmallDB m) => Integer -> m ()
add_rel2 value = modify (\db -> db{ rel2 = Set.insert value (rel2 db)})




More information about the template-haskell mailing list