Difference between revisions of "Poor man's here document"

From HaskellWiki
Jump to navigation Jump to search
 
(→‎Quasiquoting: update code for recent GHC)
 
(11 intermediate revisions by 7 users not shown)
Line 1: Line 1:
  +
== Poor man's heredoc / here document ==
 
<haskell>
 
<haskell>
 
 
main = do
 
main = do
 
doc <- here "DATA" "Here.hs" [("variable","some"),("substitution","variables")]
 
doc <- here "DATA" "Here.hs" [("variable","some"),("substitution","variables")]
Line 47: Line 47:
 
</haskell>
 
</haskell>
   
  +
== Even poorer man's here-doc / here-document ==
See Also
 
  +
  +
If you're just looking to define a multiline string constant, you can just say:
  +
  +
<haskell>
  +
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."
  +
]
  +
</haskell>
  +
  +
You can fake interpolation with:
  +
<haskell>
  +
hereDocPraise :: String -> String
  +
hereDocPraise lang = unlines [
  +
"The language with the best here-document support",
  +
"in my opinion is " ++ lang ++ "."
  +
]
  +
</haskell>
  +
  +
===Disadvantages to poorer man's here-docs===
  +
* You still need to escape special characters.
  +
* It ends with a newline whether you want one or not.
  +
  +
== Quasiquoting ==
  +
  +
<haskell>-- 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"
  +
  +
-}</haskell>
   
  +
==See also==
[http://groups.google.de/group/fa.haskell/msg/bb29c1797fe19caf Poor Man's Heredoc, as originally posted by Claus Reinke to Haskell Cafe]
 
  +
* [[String interpolation]]
 
* [http://groups.google.de/group/fa.haskell/msg/bb29c1797fe19caf Poor Man's Heredoc, as originally posted by Claus Reinke to Haskell Cafe]
  +
* http://en.wikipedia.org/wiki/Here_document
  +
* [[Quasiquotation]]

Latest revision as of 01:17, 3 January 2012

Poor man's heredoc / here document

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

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

  • You still need to escape special characters.
  • It ends with a newline whether you want one or not.

Quasiquoting

-- 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"

-}

See also