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

Viktor Dukhovni ietf-dane at dukhovni.org
Mon Nov 20 19:47:39 UTC 2023


It looks like there's some sort of syntax conflict between CPP and
long string literals folded across multiple lines.  Is there a
way to have both CPP and folded long string literals?

    $ cat /tmp/foo.hs
    {-# LANGUAGE CPP #-}
    module Main(main) where

    hello :: String
    hello = "Hello\
            \ World!"

    main :: IO ()
    main = print hello

    ----

    $ ghci /tmp/foo.hs
    GHCi, version 9.8.1: https://www.haskell.org/ghc/  :? for help
    [1 of 2] Compiling Main             ( /tmp/foo.hs, interpreted )

    /tmp/foo.hs:5:25: error: [GHC-21231]
        lexical error in string/character literal at character 'W'
      |
    5 | hello = "Hello\
      |                         ^
    Failed, no modules loaded.
    λ>
    Leaving GHCi.

When I run the input through "cpp -E" I get:

    {-# LANGUAGE CPP #-}
    module Main(main) where

    hello :: String
    hello = "Hello        \ World!"


    main :: IO ()
    main = print hello

Clearly not what I want, so the subsequent lexical error from GHC is not
surprising, but is there a workaround that allows folding long strings
across lines and retaining the layout.

Given that the CPP lexer also recognises quoted strings, it looks like a
difficult to reconcile mismatch.  There would need be some other sort of
joiner understood by GHC, where each string fragment is fully enclosed
in quotes.  Would the below be acceptable?

    {-# LANGUAGE CPP #-}
    module Main(main) where

    hello :: String
    hello = ##"Hello"\
            ##"World!"

    main :: IO ()
    main = print hello

This is turned by CPP into either (version-dependent):

    {-# LANGUAGE CPP #-}
    module Main(main) where

    hello :: String
    hello = ##"Hello"
            ##"World!"

            main :: IO ()
            main = print hello

or:

    {-# LANGUAGE CPP #-}
    module Main(main) where

    hello :: String
    hello = ##"Hello" ##"World!"


    main :: IO ()
    main = print hello

which (or some suitable variant?) GHC could then also recognise as multiple
fragments of the same single string literal?

-- 
    Viktor.


More information about the Haskell-Cafe mailing list