less prototype, less bad code implementation of CCHM type theory
You can not select more than 25 topics Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.

157 lines
4.6 KiB

  1. {
  2. module Presyntax.Lexer where
  3. import qualified Data.ByteString.Lazy as Lbs
  4. import qualified Data.Text.Encoding as T
  5. import qualified Data.Text as T
  6. import Presyntax.Tokens
  7. import Debug.Trace
  8. }
  9. %wrapper "monadUserState-bytestring"
  10. $alpha = [a-zA-Z]
  11. $digit = [0-9]
  12. $white_nol = $white # \n
  13. tokens :-
  14. $white_nol+ ;
  15. "--" .* \n ;
  16. <0,prtext> $alpha [$alpha $digit \_ \']* { variableOrKeyword }
  17. -- zero state: normal lexing
  18. <0> \= { always TokEqual }
  19. <0> \: { always TokColon }
  20. <0> \, { always TokComma }
  21. <0> \* { always TokStar }
  22. <0> ".1" { always TokPi1 }
  23. <0> ".2" { always TokPi2 }
  24. <0> \\ { always TokLambda }
  25. <0> "->" { always TokArrow }
  26. <0> \( { always TokOParen }
  27. <0> \{ { always TokOBrace }
  28. <0> \[ { always TokOSquare }
  29. <0> \) { always TokCParen }
  30. <0> \} { always TokCBrace }
  31. <0> \] { always TokCSquare }
  32. <0> \; { always TokSemi }
  33. <0> \n { just $ pushStartCode newline }
  34. <0> "&&" { always TokAnd }
  35. <0> "||" { always TokOr }
  36. <0> "{-" { just $ pushStartCode comment }
  37. <comment> {
  38. "-}" { \i l -> popStartCode *> skip i l }
  39. . ;
  40. }
  41. <0> "{-#" { \i l -> pushStartCode prkw *> always TokOPragma i l }
  42. <prkw> "PRIMITIVE" { \i l -> popStartCode *> pushStartCode prtext *> always TokPrim i l }
  43. <prtext> "#-}" { \i l -> popStartCode *> always TokCPragma i l }
  44. <0> ":let" { always TokReplLet }
  45. <0> ":t"("y"|"yp"|"ype"|()) { yield TokReplT }
  46. -- newline: emit a semicolon when de-denting
  47. <newline> {
  48. \n ;
  49. () { offsideRule }
  50. }
  51. -- layout: indentation of the next token is context for offside rule
  52. <layout> {
  53. \n ;
  54. () { startLayout }
  55. }
  56. <empty_layout> () { emptyLayout }
  57. {
  58. alexEOF :: Alex Token
  59. alexEOF = do
  60. (AlexPn _ l c, _, _, _) <- alexGetInput
  61. pure $ Token TokEof l c
  62. yield k (AlexPn _ l c, _, s, _) i = pure (Token (k $! (T.decodeUtf8 (Lbs.toStrict (Lbs.take i s)))) l c)
  63. always :: TokenClass -> AlexInput -> Int64 -> Alex Token
  64. always k x i = yield (const k) x i
  65. data AlexUserState = AlexUserState { layoutColumns :: [Int], startCodes :: [Int], leastColumn :: Int }
  66. alexInitUserState = AlexUserState [1] [] 0
  67. just :: Alex a -> AlexAction Token
  68. just k _ _ = k *> alexMonadScan
  69. getUserState :: Alex AlexUserState
  70. getUserState = Alex $ \s -> Right (s, alex_ust s)
  71. mapUserState :: (AlexUserState -> AlexUserState) -> Alex ()
  72. mapUserState k = Alex $ \s -> Right (s { alex_ust = k $! alex_ust s }, ())
  73. pushStartCode :: Int -> Alex ()
  74. pushStartCode c = do
  75. sc <- alexGetStartCode
  76. mapUserState $ \s -> s { startCodes = sc:startCodes s }
  77. alexSetStartCode c
  78. popStartCode :: Alex ()
  79. popStartCode = do
  80. sc <- startCodes <$> getUserState
  81. case sc of
  82. [] -> alexSetStartCode 0
  83. (x:xs) -> do
  84. mapUserState $ \s -> s { startCodes = xs }
  85. alexSetStartCode x
  86. offsideRule :: AlexInput -> Int64 -> Alex Token
  87. offsideRule (AlexPn _ line col, _, s, _) _
  88. | Lbs.null s = pure (Token TokEof line col)
  89. | otherwise = do
  90. popStartCode
  91. ~(col':ctx) <- layoutColumns <$> getUserState
  92. case col `compare` col' of
  93. EQ -> pure (Token TokSemi line col)
  94. GT -> alexMonadScan
  95. LT -> do
  96. mapUserState $ \s -> s { layoutColumns = ctx }
  97. pure (Token TokLEnd line col)
  98. emptyLayout :: AlexInput -> Int64 -> Alex Token
  99. emptyLayout (AlexPn _ line col, _, _, _) _ = do
  100. popStartCode
  101. pushStartCode newline
  102. pure (Token TokLEnd line col)
  103. startLayout :: AlexInput -> Int64 -> Alex Token
  104. startLayout (AlexPn _ line col, _, s, _) size = do
  105. popStartCode
  106. least <- leastColumn <$> getUserState
  107. ~(col':_) <- layoutColumns <$> getUserState
  108. if (col' >= col) || col <= least
  109. then pushStartCode empty_layout
  110. else mapUserState $ \s -> s { layoutColumns = col:layoutColumns s }
  111. pure (Token TokLStart line col)
  112. variableOrKeyword :: AlexAction Token
  113. variableOrKeyword (AlexPn _ l c, _, s, _) size =
  114. let text = T.decodeUtf8 (Lbs.toStrict (Lbs.take size s)) in
  115. case T.unpack text of
  116. "as" -> pure (Token TokAs l c)
  117. "in" -> pure (Token TokIn l c)
  118. "let" -> do
  119. pushStartCode layout
  120. mapUserState $ \s -> s { leastColumn = c }
  121. pure (Token TokLet l c)
  122. _ -> pure (Token (TokVar text) l c)
  123. }