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@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@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@ganon a]$ -----------------------------------------------------------------------------

Matt Morrow wrote:
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. ;)
Cool. Is there any progress on getting GHC to *not* freak out when you ask it to compile a CAF containing several hundred KB of string literal? :-}

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. ;) (...)
Cool!!! How exactly QuasiQuote behave, and what is available to handle them? (Or: can I find information already on the web?) Sugestion: what about tex like syntax, i.e., change of line is a space, blank line is a newline (so that we could reformat the string without changing content)? Best, MaurĂcio

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@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@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@ganon a]$ ----------------------------------------------------------------------------- _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 10/13/08, Andrew Coppin wrote:
Cool. Is there any progress on getting GHC to *not* freak out when you ask it to compile a CAF containing several hundred KB of string literal? :-}
Yes and no. There's dons' compiled-constants pkg which has a solution: http://code.haskell.org/~dons/code/compiled-constants/ And the code below would do all the haskell-side work for importing the data from C, but I'm not aware of a way to have ghc not freak out if it has to compile a huge amount of static data. ------------------------------------------------------------------------------- {-# LANGUAGE TemplateHaskell #-} module FromC (fromC) where import GHC.Ptr(Ptr(Ptr)) import Foreign.C.Types(CChar) import System.IO.Unsafe(unsafePerformIO) import Data.ByteString.Unsafe(unsafePackAddressLen) import Data.ByteString(ByteString) import Language.Haskell.TH.Syntax import Language.Haskell.TH.Lib -- | -- If in asdf.c == @unsigned char stuff[1024] = {42,.....,19};@, then -- -- > $(fromC "./asdf.c" "stuff" "dat") --- -- will produce: -- -- > foreign import ccall unsafe "&" stuff :: Ptr CChar -- > dat :: ByteString -- > dat = unsafePerformIO (case stuff of -- > Ptr addr_0 -> unsafePackAddressLen 1024 addr_0) -- fromC :: FilePath -> String -> Int -> String -> Q [Dec] fromC cfile cvar bytes hsvar = do let hsname = mkName hsvar t <- [t|ByteString|] e <- [|unsafePerformIO (case $(varE . mkName $ cvar) of Ptr addr -> unsafePackAddressLen bytes addr) |] return [ ForeignD (ImportF CCall Unsafe "&" (mkName cvar) (AppT (ConT ''Ptr) (ConT ''CChar))) , SigD hsname t , ValD (VarP hsname) (NormalB e) []] -------------------------------------------------------------------------------

mjm2002:
On 10/13/08, Andrew Coppin wrote:
Cool. Is there any progress on getting GHC to *not* freak out when you ask it to compile a CAF containing several hundred KB of string literal? :-}
Yes and no. There's dons' compiled-constants pkg which has a solution:
http://code.haskell.org/~dons/code/compiled-constants/
And the code below would do all the haskell-side work for importing the data from C, but I'm not aware of a way to have ghc not freak out if it has to compile a huge amount of static data.
Hiding it inside an unboxed string constant? i.e. "this be bits"# Or does GHC still freak? - Don

Don Stewart wrote:
mjm2002:
On 10/13/08, Andrew Coppin wrote:
Cool. Is there any progress on getting GHC to *not* freak out when you ask it to compile a CAF containing several hundred KB of string literal? :-} Yes and no. There's dons' compiled-constants pkg which has a solution:
http://code.haskell.org/~dons/code/compiled-constants/
And the code below would do all the haskell-side work for importing the data from C, but I'm not aware of a way to have ghc not freak out if it has to compile a huge amount of static data.
Hiding it inside an unboxed string constant? i.e.
"this be bits"#
Or does GHC still freak?
This is the trick I use in Haddock and Alex, it should work fine. I don't know why GHC should have any problems with larger string literals anyway, since they get compiled into x = unpackCString "..."# if you have evidence to the contrary, please submit a bug report. (lists of other things are a different matter, which we already have open bugs for). Cheers, Simon

How exactly QuasiQuote behave, and what is available to handle them? (Or: can I find information already on the web?)
A QuasiQuoter is data QuasiQuoter = QuasiQuoter {quoteExp :: String -> Q Exp, quotePat :: String -> Q Pat} -- Defined in Language.Haskell.TH.Quote There is a good writeup on the haskell.org wiki, and a link to a paper there.
Sugestion: what about tex like syntax, i.e., change of line is a space, blank line is a newline (so that we could reformat the string without changing content)?
GHC hands you a String, and you can do arbitrary things with it before you eventually return either an ExpQ or PatQ (depending on context). I've uploaded a few QQs to hackage http://hackage.haskell.org/cgi-bin/hackage-scripts/package/regexqq http://hackage.haskell.org/cgi-bin/hackage-scripts/package/lighttpd-conf-qq and am working on both one for Haskell itself, as well as as for Javascript.
Best, MaurĂcio
Matt
participants (6)
-
Andrew Coppin
-
Don Stewart
-
L.Guo
-
Matt Morrow
-
Mauricio
-
Simon Marlow