Re: [Haskell-cafe] how to generate source code from TH Exp?

2011-05-12 Thread Daniel Fischer
On Thursday 12 May 2011 19:14:09, Felipe Almeida Lessa wrote:
> On Thu, May 12, 2011 at 2:04 PM, Stefan Kersten  wrote:
> > extractModules = sort . nub . everything (++) ([] `mkQ` f)
> > where f (NameQ x) = [modString x]
> >   f (NameG _ _ x) = [modString x]
> >   f _ = []
> 
> Minor nitpick:  instead of doing 'sort . nub', please use 'import
> qualified Data.Set as S' and do 'S.toAscList . S.fromList'.  This
> should be a lot faster.

Or `map head . group . sort', which may be faster than building an 
intermediate Set (haven't benchmarked, may be faster, slower or mkae no 
difference).

> 
> Cheers, =)

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] how to generate source code from TH Exp?

2011-05-12 Thread Felipe Almeida Lessa
On Thu, May 12, 2011 at 2:04 PM, Stefan Kersten  wrote:
> extractModules = sort . nub . everything (++) ([] `mkQ` f)
>     where f (NameQ x) = [modString x]
>           f (NameG _ _ x) = [modString x]
>           f _ = []

Minor nitpick:  instead of doing 'sort . nub', please use 'import
qualified Data.Set as S' and do 'S.toAscList . S.fromList'.  This
should be a lot faster.

Cheers, =)

-- 
Felipe.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] how to generate source code from TH Exp?

2011-05-12 Thread Stefan Kersten

On 5/12/11 4:03 PM, Serguey Zefirov wrote:

Just pretty-print a Exp.

It seems that "show $ ppr exp" will produce exactly what you need.

The same goes for Dec (declarations), etc.


ah ok, thanks!

fwiw, here's a way to extract a list of module names that need to be 
imported, adapted from an example by Neil Mitchell using generics:


extractModules :: Data a => a -> [String]
extractModules = sort . nub . everything (++) ([] `mkQ` f)
 where f (NameQ x) = [modString x]
   f (NameG _ _ x) = [modString x]
   f _ = []

which can be used to output a source code module:

mkModule :: (Data a, Ppr a) => [String] -> String -> a -> String
mkModule exts name e =
unlines ([ "{-# LANGUAGE " ++ intercalate ", " exts ++ " #-}"
 , "module " ++ name ++ " where" ]
 ++ map ("import qualified " ++) (extractModules e))
 ++ show (ppr e)

good enough for now ;)



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] how to generate source code from TH Exp?

2011-05-12 Thread Serguey Zefirov
Just pretty-print a Exp.

It seems that "show $ ppr exp" will produce exactly what you need.

The same goes for Dec (declarations), etc.

2011/5/12 Stefan Kersten :
> hi,
>
> i was wondering if it's possible to directly generate Haskell source code
> from a Template Haskell `Q Exp', i.e. use TH as a kind of preprocessor? i am
> asking because currently the iOS port of ghc doesn't support TH and i need
> to generate some instances for the persistent package [1,2].
>
> i've been toying with
>
> fmap ppr . runQ $ q
>
> but the result needs to be edited by hand quite a bit. any ideas where to
> start?
>
> thanks,
> 
>
> [1] http://hackage.haskell.org/package/persistent
> [2] http://hackage.haskell.org/package/persistent-template
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] how to generate source code from TH Exp?

2011-05-12 Thread Stefan Kersten

hi,

i was wondering if it's possible to directly generate Haskell source 
code from a Template Haskell `Q Exp', i.e. use TH as a kind of 
preprocessor? i am asking because currently the iOS port of ghc doesn't 
support TH and i need to generate some instances for the persistent 
package [1,2].


i've been toying with

fmap ppr . runQ $ q

but the result needs to be edited by hand quite a bit. any ideas where 
to start?


thanks,


[1] http://hackage.haskell.org/package/persistent
[2] http://hackage.haskell.org/package/persistent-template

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe