Skip to content
Snippets Groups Projects
Commit 5eb1e883 authored by Alexander Kaznacheev's avatar Alexander Kaznacheev
Browse files

fix MultilineStrings with let

parent d44f1741
No related branches found
No related tags found
No related merge requests found
......@@ -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
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment