diff --git a/compiler/GHC/Driver/MultilineStrings.hs b/compiler/GHC/Driver/MultilineStrings.hs index e1088c728b4be283d3a7ee35d9db7c71de17c1e1..fcc00ae7fba4e9a81d9af94d9c41466b477a01cf 100644 --- a/compiler/GHC/Driver/MultilineStrings.hs +++ b/compiler/GHC/Driver/MultilineStrings.hs @@ -3,30 +3,32 @@ module GHC.Driver.MultilineStrings where import GHC.Prelude convertMultilineStrings :: String -> String -convertMultilineStrings s = go s WaitingForString +convertMultilineStrings s = go s WaitingForString 0 where - go s state = case state of + go s state charCnt = case state of WaitingForString -> case s of "" -> "" '-':'-':s -> '-':'-': skipOneLineComment s '{':'-':s -> '{':'-': skipComment s - '"':'"':'"':'\n':'"':'"':'"':s -> '"':'"': go s state - '"':'"':'"':'\n':s -> '\n':' ':'"' : go s InString - c:s -> c : go s state + '"':'"':'"':'\n':'"':'"':'"':s -> '"':'"': go s state 3 + '"':'"':'"':'\n':s -> '\n':' ':'"' : go s InString charCnt + '\n':s -> '\n' : go s state 0 + c:s -> c : go s state (charCnt + 1) InString -> case s of "" -> error "we are in a mutline string, but text ended unexpectedly" - '\n':'"':'"':'"':s -> '"':'\n' : go s WaitingForString - '"':s -> '\\':'"' : go s state - '\\':s -> '\\':'\\' : go s state - '\n':s -> '\\':'n':'"':'\n':' ':'+':'+':' ':'"' : go s state - c:s -> c : go s state + '\n':'"':'"':'"':s -> '"':'\n' : go s WaitingForString 0 + '"':s -> '\\':'"' : go s state charCnt + '\\':s -> '\\':'\\' : go s state charCnt + -- '\n':s -> '\\':'n':'"':'\n':' ':'+':'+':' ':'"' : go s state charCnt + '\n':s -> "\\n\"\n" ++ replicate charCnt ' ' ++ " ++ \"" ++ go s state charCnt + c:s -> c : go s state charCnt where - skipOneLineComment "" = go "" state - skipOneLineComment s@('\n':_) = go s state + skipOneLineComment "" = go "" state charCnt + skipOneLineComment s@('\n':_) = go s state charCnt skipOneLineComment (c:s) = c : skipOneLineComment s - skipComment "" = go "" state - skipComment ('-':'}':s) = '-':'}': go s state + skipComment "" = go "" state charCnt + skipComment ('-':'}':s) = '-':'}': go s state charCnt skipComment (c:s) = c : skipComment s data State