how to generate source code from TH Exp?

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, <sk> [1] http://hackage.haskell.org/package/persistent [2] http://hackage.haskell.org/package/persistent-template

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, <sk>
[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

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 ;) <sk>

On Thu, May 12, 2011 at 2:04 PM, Stefan Kersten
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.

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, =)

On Thu, 2011-05-12 at 19:31 +0200, Daniel Fischer wrote:
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).
if the input list has _many_ duplicates, wouldn't using 'map head . group . sort' require more memory than going the 'toAscList . fromList' way?

On Sunday 15 May 2011 15:32:03, Herbert Valerio Riedel wrote:
On Thu, 2011-05-12 at 19:31 +0200, Daniel Fischer wrote:
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).
if the input list has _many_ duplicates, wouldn't using 'map head . group . sort' require more memory than going the 'toAscList . fromList' way?
Good point. Yes, it would (consider `replicate maxBound 1'). So `map head . group . sort' might be faster for lists with few duplicates, but it has worse worst-case complexity, so it's safer to use `toAscList . fromList'. Even in the where it's slower, it probably wouldn't make too much of a difference.
participants (5)
-
Daniel Fischer
-
Felipe Almeida Lessa
-
Herbert Valerio Riedel
-
Serguey Zefirov
-
Stefan Kersten