How to use Lexer.lexer to produce closing braces as well?
Kwanghoon Choi
lazyswamp at gmail.com
Wed Aug 18 14:20:54 UTC 2021
Hi,
I have recently been playing with GHC's Lexer.lexer in the ghc-parser-lib
package.
Given
module HelloWorld where
main = putStrLn "Hello World!\n"
it produces
stack exec -- lexer-exe ./examples/HelloWorld.hs
Lexing&Parsing: ./examples/HelloWorld.hs
module at (1, 1): module
CONID at (1, 8): CONID
where at (1, 19): where
vocurly at (3, 1): vocurly <==== { is inserted automatically!!
VARID at (3, 1): VARID
= at (3, 6): =
VARID at (3, 8): VARID
STRING at (3, 17): STRING
; at (4, 1): ;
By the example above, the lexer automatically inserts an opening brace
(i.e. vocurly) right after 'where'. But it does not insert a matching
closing brace (i.e., vccurly), which would lead to a failure in parsing a
list of tokens produced by the lexer.
My question is how to use the GHC lexer to produce closing braces as well.
All my code is available
- https://github.com/kwanghoon/hslexer
To save your time, the relevant part of the code is as follows:
In app/HaskellLexer.hs,
singleHaskellToken :: P (Located Token)
singleHaskellToken =
Lexer.lexer False
(\locatedToken -> P (\pstate -> POk pstate locatedToken))
tokInfos :: [Terminal Token] -> P (Line, Column, [Terminal Token])
tokInfos s = do
locatedToken <- singleHaskellToken
case locatedToken of
L srcspan ITeof ->
let (start_line, start_col, end_line, end_col) = srcSpanToLineCol
srcspan in
return (end_line, end_col, s)
L srcspan tok ->
let (start_line, start_col, end_line, end_col) = srcSpanToLineCol
srcspan in
tokInfos (Terminal (fromToken tok) start_line start_col (Just
tok) : s)
Thanks in advance
Best regards,
Kwanghoon
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20210818/aa1e791a/attachment.html>
More information about the ghc-devs
mailing list