[Haskell-cafe] Folded long string literals and CPP?

Evan Laforge qdunkan at gmail.com
Thu Nov 23 16:21:56 UTC 2023


I switched to cpphs which doesn't have this problem.

On Wed, Nov 22, 2023, 10:42 PM Viktor Dukhovni <ietf-dane at dukhovni.org>
wrote:

> On Tue, Nov 21, 2023 at 05:36:13PM -0800, Jeff Clites via Haskell-Cafe
> wrote:
>
> > I like it. I would be interesting (though perhaps overkill) to have a
> special operator which is like ++ but which can only be applied to list
> literals (not only strings), and which is guaranteed to be syntactic sugar
> for the concatenated list. One step fancier would be to allow it not just
> for literals but for any known-at-compile-time values. (So it’s
> syntactically an operator but in actuality more of a compiler directive, to
> evaluate the concatenation at compile time, or fail if that’s not possible.)
>
> Well, I guess we already have that in the form of Template Haskell
> splices, but that's rather a heavy hammer to swat this particular
> fly...
>
>     {-# LANGUAGE TemplateHaskell #-}
>     module Data.CompileTime(compileTimeString) where
>     import Language.Haskell.TH.Syntax as TH
>
>     compileTimeString :: TH.Quote m => String -> TH.Code m String
>     compileTimeString str = let !lit = str in [|| lit ||]
>
> Which when imported into:
>
>     {-# LANGUAGE CPP, TemplateHaskell #-}
>     module Main(main) where
>     import Data.CompileTime
>
>     hello :: String
>     hello = $$( compileTimeString $ "Hello" ++ " World!" )
>
>     main :: IO ()
>     main = print hello
>
> Produces the "Core" below:
>
>     ...
>     main :: IO ()
>     main
>       = print ($fShowList $fShowChar) (unpackCString# "Hello World!"#)
>
> --
>     Viktor.
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20231123/7783a0aa/attachment.html>


More information about the Haskell-Cafe mailing list