[Haskell-cafe] Re: Scraping boilerplate deriving?

Kevin Jardine kevinjardine at gmail.com
Tue Sep 14 12:52:56 EDT 2010


OK, thanks for everyone's help!

Serguey's code works very well now.

Kevin

On Sep 14, 6:14 pm, Erik Hesselink <hessel... at gmail.com> wrote:
> Yes, if you use template haskell, all top level functions and values
> have to be defined before you use them.
>
> Erik
>
>
>
> On Tue, Sep 14, 2010 at 18:11, Kevin Jardine <kevinjard... at gmail.com> wrote:
> > Hmm - It seems to work if the code is defined before my main function
> > and not after it.
>
> > Does this have to do with TH being part of the compile process and so
> > the order matters?
>
> > Kevin
>
> > On Sep 14, 6:03 pm, Kevin Jardine <kevinjard... at gmail.com> wrote:
> >> Thanks Serguey!
>
> >> The library code compiles, but when I try to use it in client code:
>
> >> a. I get:
>
> >> Not in scope: type constructor or class 'A'
>
> >> and even stranger,
>
> >> b. GHC cannot find any of my code after the
>
> >> $(mkNewType "A")
>
> >> and claims that all the functions I defined there are also not in
> >> scope.
>
> >> Any ideas?
>
> >> The CPP solution works but Template Haskell is definitely cooler, so
> >> it would be great to get this to work!
>
> >> Kevin
>
> >> On Sep 14, 2:29 pm,  Zefirov <sergu... at gmail.com> wrote:
>
> >> > 2010/9/14 Kevin Jardine <kevinjard... at gmail.com>:
>
> >> > > I would like to use some macro system (perhaps Template Haskell?) to
> >> > > reduce this to something like
>
> >> > > defObj MyType
>
> >> > > I've read through some Template Haskell documentation and examples,
> >> > > but I find it intimidatingly hard to follow. Does anyone has some code
> >> > > suggestions or pointers to something similar?
>
> >> > The solutions first:
> >> > -------------------------------------------------
> >> > {-# LANGUAGE TemplateHaskell #-}
>
> >> > module T(mkNewType) where
>
> >> > import Language.Haskell.TH
>
> >> > decls = [d|newtype TempDecl = TempDecl Int deriving (Eq,Ord,Show)|]
> >> > decl = do
> >> >         [d] <- decls
> >> >         runIO $ print d -- just to show inetrnals
> >> >         return d
>
> >> > mkNewType :: String -> Q [Dec]
> >> > mkNewType n = do
> >> >         d <- decl
> >> >         let name = mkName n
> >> >         return $ (\x -> [x]) $ case d of
> >> >                 (NewtypeD cxt _ argvars (NormalC _ args) derivings) ->
> >> >                         NewtypeD cxt name argvars (NormalC name args) derivings
> >> > --------------------------------------
> >> > I took perfectly valid declaration, dissected it using case analysis
> >> > and changed relevant parts.
>
> >> > And an example client:
> >> > -------------------------------------
> >> > {-# LANGUAGE TemplateHaskell #-}
>
> >> > import T
>
> >> > $(mkNewType "A")
> >> > -------------------------------------
> >> > It all work together.
>
> >> > I studied how to use Template Haskell that way: I obtained
> >> > declarations of what I need, printed them and looked through
> >> > documentation for relevant data types and constructors. It's not
> >> > harder that any other library in Haskell, actually.
> >> > _______________________________________________
> >> > Haskell-Cafe mailing list
> >> > Haskell-C... at haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
>
> >> _______________________________________________
> >> Haskell-Cafe mailing list
> >> Haskell-C... at haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
> > _______________________________________________
> > Haskell-Cafe mailing list
> > Haskell-C... at haskell.org
> >http://www.haskell.org/mailman/listinfo/haskell-cafe
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-C... at haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe


More information about the Haskell-Cafe mailing list