Poor man's here document
Poor man's heredoc / here document[edit]
main = do
doc <- here "DATA" "Here.hs" [("variable","some"),("substitution","variables")]
putStrLn doc
html <- here "HTML" "Here.hs" [("code",doc)]
putStrLn html
here tag file env = do
txt <- readFile file
let (_,_:rest) = span (/="{- "++tag++" START") (lines txt)
(doc,_) = span (/=" "++tag++" END -}") rest
return $ unlines $ map subst doc
where
subst ('$':'(':cs) = case span (/=')') cs of
(var,')':cs) -> maybe ("$("++var++")") id (lookup var env) ++ subst cs
_ -> '$':'(':subst cs
subst (c:cs) = c:subst cs
subst "" = ""
{- DATA START
this is a poor man's here-document
with quotes ", and escapes \,
and line-breaks, and layout
without escaping \" \\ \n,
without concatenation.
oh, and with $(variable) $(substitution), $(too).
DATA END -}
{- HTML START
<html>
<head><title>very important page</title></head>
<body>
<verb>
$(code)
</verb>
</body>
</html>
HTML END -}
Even poorer man's here-doc / here-document[edit]
If you're just looking to define a multiline string constant, you can just say:
str :: String
str = unlines [
"Here's a multiline string constant.",
"\tIt's not as convenient as Perl's here-documents,",
"\tbut it does the trick for me."
]
You can fake interpolation with:
hereDocPraise :: String -> String
hereDocPraise lang = unlines [
"The language with the best here-document support",
"in my opinion is " ++ lang ++ "."
]
Disadvantages to poorer man's here-docs[edit]
- You still need to escape special characters.
- It ends with a newline whether you want one or not.
Quasiquoting[edit]
-- Str.hs
module Str(str) where
import Language.Haskell.TH
import Language.Haskell.TH.Quote
str = QuasiQuoter { quoteExp = stringE }
-- Main.hs
{-# LANGUAGE QuasiQuotes #-}
module Main where
import Str
foo = [str|This is a multiline string.
It's many lines long.
It contains embedded newlines. And weird stuff:
łe¶→łeđø→ħe¶ŋø→nđe”øn
It ends here: |]
main = putStrLn foo
-- ghci Str.hs -XQuasiQuotes
{-
-- Note we can only do single-line quotations here
*Str> [str|foo bar baz|]
"foo bar baz"
-}