[Haskell-cafe] Multi-line string literals are both easy /and/elegant in Haskell

L.Guo leaveye.guo at gmail.com
Mon Oct 13 22:35:56 EDT 2008


Oh, that's so cool.

But, this feather is too difficult to be configured in UE32 -- my costom IDE.

Pity. Hopes I wouldn't forget it later.

------------------				 
L.Guo
2008-10-14

-------------------------------------------------------------
From: Matt Morrow
At: 2008-10-14 02:15:30
Subject: [Haskell-cafe] Multi-line string literals are both easy /and/elegant in Haskell

The new QuasiQuotes extension arriving with ghc 6.10 is very exciting,
and handling multi-line string literals is like stealing candy from
a baby. ;)

-----------------------------------------------------------------------------
-- Here.hs
module Here (here) where

import Language.Haskell.TH.Quote
import Language.Haskell.TH.Syntax
import Language.Haskell.TH.Lib

here :: QuasiQuoter
here = QuasiQuoter (litE . stringL) (litP . stringL)
-----------------------------------------------------------------------------

-----------------------------------------------------------------------------
-- There.hs
{-# LANGUAGE QuasiQuotes #-}
module Main where
import Here (here)
main = putStr [$here|

Shall I say, I have gone at dusk through narrow streets
And watched the smoke that rises from the pipes
Of lonely men in shirt-sleeves, leaning out of windows?

I should have been a pair of ragged claws
Scuttling across the floors of silent seas.


|]
-----------------------------------------------------------------------------

-----------------------------------------------------------------------------
[m at ganon a]$ ghc -O2 --make There.hs
[1 of 2] Compiling Here             ( Here.hs, Here.o )
[2 of 2] Compiling Main             ( There.hs, There.o )
Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
Loading package syb ... linking ... done.
Loading package array-0.2.0.0 ... linking ... done.
Loading package packedstring-0.1.0.1 ... linking ... done.
Loading package containers-0.2.0.0 ... linking ... done.
Loading package pretty-1.0.1.0 ... linking ... done.
Loading package template-haskell ... linking ... done.
Linking There ...
[m at ganon a]$ ./There


Shall I say, I have gone at dusk through narrow streets
And watched the smoke that rises from the pipes
Of lonely men in shirt-sleeves, leaning out of windows?

I should have been a pair of ragged claws
Scuttling across the floors of silent seas.


[m at ganon a]$
-----------------------------------------------------------------------------
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe at haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



More information about the Haskell-Cafe mailing list