
I couldn't find a compile-time here document facility, so I wrote one using Template Haskell:
module HereDocs(hereDocs) where
import Control.Exception import Language.Haskell.TH.Syntax
getDoc :: String -> [String] -> (String,[String]) getDoc eof txt = let (doc,rest) = break (== eof) txt in (unlines doc, drop 1 rest)
makeVal :: String -> String -> [Dec] makeVal var doc = let name = mkName var in [SigD name (ConT (mkName "String")), ValD (VarP name) (NormalB (LitE (StringL doc))) []]
scanSrc :: [Dec] -> [String] -> Q [Dec] scanSrc vals [] = return vals scanSrc vals (x:xs) = case words x of [var, "=", ('<':'<':eof)] -> let (doc,rest) = getDoc eof xs val = makeVal var doc in scanSrc (vals ++ val) rest _ -> scanSrc vals xs
hereDocs :: FilePath -> Q [Dec] hereDocs src = let fin = catchJust assertions (evaluate src) (return.takeWhile (/= ':')) in runIO (fin >>= readFile >>= return . lines) >>= scanSrc []
One binds here documents embedded in comments by writing
import HereDocs $(hereDocs "Main.hs")
As an idiom, one can refer to the current file as follows; the first thing hereDocs does is catch assert errors in order to learn the file name:
import HereDocs $(hereDocs $ assert False "")
Here is an example use:
{-# OPTIONS_GHC -fth -Wall -Werror #-}
module Main where
import System import Control.Exception
import HereDocs $(hereDocs $ assert False "")
{- ruby = <
lisp = <
exec :: FilePath -> String -> IO ExitCode exec fout str = do writeFile fout str system ("chmod +x " ++ fout ++ "; ./" ++ fout)
main :: IO ExitCode main = do exec "hello.rb" ruby exec "hello.scm" lisp

bayer:
I couldn't find a compile-time here document facility, so I wrote one using Template Haskell:
Very nice! You should wrap it in a little .cabal file, and upload it to hackage.haskell.org, so we don't forget about it. Details on cabalising and uploading here: http://haskell.org/haskellwiki/How_to_write_a_Haskell_program http://cgi.cse.unsw.edu.au/~dons/blog/2006/12/11 -- Don
module HereDocs(hereDocs) where
import Control.Exception import Language.Haskell.TH.Syntax
getDoc :: String -> [String] -> (String,[String]) getDoc eof txt = let (doc,rest) = break (== eof) txt in (unlines doc, drop 1 rest)
makeVal :: String -> String -> [Dec] makeVal var doc = let name = mkName var in [SigD name (ConT (mkName "String")), ValD (VarP name) (NormalB (LitE (StringL doc))) []]
scanSrc :: [Dec] -> [String] -> Q [Dec] scanSrc vals [] = return vals scanSrc vals (x:xs) = case words x of [var, "=", ('<':'<':eof)] -> let (doc,rest) = getDoc eof xs val = makeVal var doc in scanSrc (vals ++ val) rest _ -> scanSrc vals xs
hereDocs :: FilePath -> Q [Dec] hereDocs src = let fin = catchJust assertions (evaluate src) (return.takeWhile (/= ':')) in runIO (fin >>= readFile >>= return . lines) >>= scanSrc []
One binds here documents embedded in comments by writing
import HereDocs $(hereDocs "Main.hs")
As an idiom, one can refer to the current file as follows; the first thing hereDocs does is catch assert errors in order to learn the file name:
import HereDocs $(hereDocs $ assert False "")
Here is an example use:
{-# OPTIONS_GHC -fth -Wall -Werror #-}
module Main where
import System import Control.Exception
import HereDocs $(hereDocs $ assert False "")
{- ruby = <
lisp = <
exec :: FilePath -> String -> IO ExitCode exec fout str = do writeFile fout str system ("chmod +x " ++ fout ++ "; ./" ++ fout)
main :: IO ExitCode main = do exec "hello.rb" ruby exec "hello.scm" lisp
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Donald Bruce Stewart
bayer:
I couldn't find a compile-time here document facility, so I wrote one using Template Haskell:
Very nice! You should wrap it in a little .cabal file, and upload it to hackage.haskell.org, so we don't forget about it.
Details on cabalising and uploading here:
http://haskell.org/haskellwiki/How_to_write_a_Haskell_program http://cgi.cse.unsw.edu.au/~dons/blog/2006/12/11
I was waiting for the other shoe to drop, as usual. I tweaked the code a bit, and I'm getting ready to contribute it to Hackage, as I find it useful. The current source can be found at http://www.math.columbia.edu/~bayer/Haskell/Annote/HereDocs.html Basically, it bothered me that I was using assert to figure out the file name (an idea that others have also had) because asserts disappear under optimization. I looked again at Control.Exception, and I realized that I would be better off catching a pattern-matching exception: $(hereDocs $ let [e] = [] in e) (Can anyone come up with a shorter pattern match failure, that can be used as a value here?) Of course, anything like this is like gas fireplace logs, pointlessly recreating the past. There is little wrong with simply hard-coding the file name; GHC has this nice way of letting me know when code like this gets out of sync: $(hereDocs "Strings.hs") So here is my question:
The source should live under a directory path that fits into the existing module layout guide. http://www.haskell.org/~simonmar/lib-hierarchy.html
A here document is a kind of data, but it is really a language extension, and one that depends on a GHC extension, Template Haskell. I'd go for Data.HereDocs but that doesn't seem quite right. The newbie in me doesn't want to park my car in your living room, so to speak. What's the right place for this?

On Jul 25, 2007, at 19:15 , Dave Bayer wrote:
A here document is a kind of data, but it is really a language extension, and one that depends on a GHC extension, Template Haskell. I'd go for
Data.HereDocs
but that doesn't seem quite right. The newbie in me doesn't want to park my car in your living room, so to speak. What's the right place for this?
This sounds to me like something that should go in Language.Haskell, since it defines a language extension and not a new data type or typeclass. Not that I have much experience in laying out Haskell libraries.... -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH
participants (4)
-
Brandon S. Allbery KF8NH
-
Dave Bayer
-
Dave Bayer
-
dons@cse.unsw.edu.au