syntax...(strings/interpolation/here docs)

C.Reinke C.Reinke@ukc.ac.uk
Thu, 14 Feb 2002 16:36:02 +0000


{-
> Unlike my rough proposal, one should aim for a combination of
> (mostly) in-Haskell implementation and (some) pre-processing.  As
> Thomas Nordin has pointed out to me in private email, Hugs (Dec
> 2001) already supports this (module lib/hugs/Quote.hs and flag +H).
>
> The real trick is to have the same support in all implementations..
-}

module HereDocuments where

{- :set +H -}
import Quote

text = ``
  When I mentioned pre-processing, I didn't mean doing something
  to generate a Haskell program, I meant simple language extension
  (as in: syntactic sugar). It is nice that the Hugs variant of
  here documents is easily implemented with pre-processing, but
  that should be done behind the scenes.

  Usually, I wouldn't make such a fuss, but here documents are really
  not some new and experimental feature. They're an old hat, and a
  very useful hat. The only question is how to integrate them into the
  rest of Haskell. The Lewis/Nordin suggestion implemented in Hugs
  looks like a good compromise, but it won't do harm to bind the sugar
  to an option/flag for a test period.

  In the end, a stable form of here documents should be part of the 
  language (not part of what you can do to it with whatever tools in
  whatever contexts), directly supported by all implementations.
  ''

main = putStrLn $ trim text

-- Claus