is there a way to pretty print a module?

is there a way to pretty print a module? like: module Main where import Language.Haskell.TH main = do print $ pprint Main

"Anatoly Yakovenko"
is there a way to pretty print a module? like:
module Main where import Language.Haskell.TH main = do print $ pprint Main
haskell-src should be able to do that. -- (c) this sig last receiving data processing entity. Inspect headers for copyright history. All rights reserved. Copying, hiring, renting, performance and/or quoting of this signature prohibited.

is there a way to pretty print a module? like:
module Main where import Language.Haskell.TH main = do print $ pprint Main
haskell-src should be able to do that.
I think haskell-src requires you to read the module at run time. I want to embed the contents of the module in my program. Basically a program that can print itself. Anatoly

On Thu, Oct 30, 2008 at 10:15 AM, Anatoly Yakovenko
is there a way to pretty print a module? like:
module Main where import Language.Haskell.TH main = do print $ pprint Main
haskell-src should be able to do that.
I think haskell-src requires you to read the module at run time. I want to embed the contents of the module in my program. Basically a program that can print itself.
Could you use haskell-src from TH and then unsafePerformIO to get the reading to work during compile time? I've done something like this in the past with Language.Haskell and TH. I described it here: http://blog.codersbase.com/2006/09/01/simple-unit-testing-in-haskell/ Maybe someone who has studied more TH knows a way to remove the unsafePerformIO. Jason

Jason Dagit wrote:
Could you use haskell-src from TH and then unsafePerformIO to get the reading to work during compile time? I've done something like this in the past with Language.Haskell and TH. I described it here: http://blog.codersbase.com/2006/09/01/simple-unit-testing-in-haskell/
Maybe someone who has studied more TH knows a way to remove the unsafePerformIO.
Replace tests :: [String] tests = unsafePerformIO $ by tests :: Q [String] tests = runIO $ and $(mkChecks tests) by $(mkChecks =<< tests) (The Q monad should really have an MonadIO instance.) HTH, Bertram

i guess am missing something: $ cat ./test.hs {-# LANGUAGE TemplateHaskell#-} module Main where import Language.Haskell.TH import qualified Data.ByteString as BS embedFile :: FilePath -> Q BS.ByteString embedFile ff = runIO $ BS.readFile ff main = do me <- runQ $ embedFile "./test.hs" print me $ ghc --make test.hs [1 of 1] Compiling Main ( test.hs, test.o ) Linking test ... $ ./test " {-# LANGUAGE TemplateHaskell#-}\nmodule Main where\n\nimport Language.Haskell.TH\nimport qualified Data.ByteString as BS\n\nembedFile :: FilePath -> Q BS.ByteString\nembedFile ff = runIO $ BS.readFile ff\n\n\nmain = do\n me <- runQ $ embedFile \"./test.hs\"\n print me\n\n" $ mv test.hs test.hs.old $ ./test test: ./test.hs: openBinaryFile: does not exist (No such file or directory) i was hoping test.hs would become part of the executable.

cool, i found this: http://www.nabble.com/template-haskell----include-a-file--td19462913.html $ cat test.hs {-# LANGUAGE TemplateHaskell#-} module Main where import Language.Haskell.TH import EmbedStr me = $(embedStr $ readFile "./test.hs") main = do print $ me $ cat EmbedStr.hs {-# LANGUAGE TemplateHaskell#-} module EmbedStr where import Language.Haskell.TH import Language.Haskell.TH.Syntax (lift) embedStr:: IO String -> ExpQ embedStr str = lift =<< runIO str

Anatoly Yakovenko wrote:
is there a way to pretty print a module? like:
module Main where import Language.Haskell.TH main = do print $ pprint Main
haskell-src should be able to do that.
I think haskell-src requires you to read the module at run time. I want to embed the contents of the module in my program. Basically a program that can print itself.
This is rather like the idea of a quine; a program the prints itself out without referring directly to its own source code. The usual Haskell quine is: putStrLn$(\s->s++show s)"putStrLn$(\\s->s++show s)" If merely returning the source code is enough then you can do: (\s->s++show s)"(\\s->s++show s)" It could be more elegant if \ weren't both lambda and string escape. -- src/

On Sun, 2008-11-02 at 19:34 +0000, Simon Richard Clarkstone wrote:
Anatoly Yakovenko wrote:
is there a way to pretty print a module? like:
module Main where import Language.Haskell.TH main = do print $ pprint Main
haskell-src should be able to do that.
I think haskell-src requires you to read the module at run time. I want to embed the contents of the module in my program. Basically a program that can print itself.
This is rather like the idea of a quine; a program the prints itself out without referring directly to its own source code. The usual Haskell quine is:
putStrLn$(\s->s++show s)"putStrLn$(\\s->s++show s)"
If merely returning the source code is enough then you can do:
(\s->s++show s)"(\\s->s++show s)"
It could be more elegant if \ weren't both lambda and string escape.
So get rid of the lambda, ap(++)show"ap(++)show"
participants (6)
-
Achim Schneider
-
Anatoly Yakovenko
-
Bertram Felgenhauer
-
Derek Elkins
-
Jason Dagit
-
Simon Richard Clarkstone