Pretty-printing TH data types
Richard Eisenberg
eir at cis.upenn.edu
Wed Nov 11 14:12:04 UTC 2015
Does this Template Haskell template work for you?
> {-# LANGUAGE TemplateHaskell #-}
>
> module TestTH where
>
> import Language.Haskell.TH.Ppr
> import Language.Haskell.TH
>
> $( do expr <- [| \x -> case x of True -> not; False -> id |]
> runIO $ putStrLn $ pprint expr
> return [] )
Richard
On Nov 11, 2015, at 6:14 AM, Jan Stolarek <jan.stolarek at p.lodz.pl> wrote:
> Devs,
>
> Module Language.Haskell.TH.Ppr defines Ppr instances for Template Haskell data types. What is the
> fastest way of testing these instances, ie. pretty-printing TH data types? I want to make sure
> that the instances I added print the data type in the way that I expect.
>
> Janek
>
> ---
> Politechnika Łódzka
> Lodz University of Technology
>
> Treść tej wiadomości zawiera informacje przeznaczone tylko dla adresata.
> Jeżeli nie jesteście Państwo jej adresatem, bądź otrzymaliście ją przez pomyłkę
> prosimy o powiadomienie o tym nadawcy oraz trwałe jej usunięcie.
>
> This email contains information intended solely for the use of the individual to whom it is addressed.
> If you are not the intended recipient or if you have received this message in error,
> please notify the sender and delete it from your system.
> _______________________________________________
> ghc-devs mailing list
> ghc-devs at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
More information about the ghc-devs
mailing list