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.

184 lines
5.3 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> \} { closeBrace }
  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. \{ { openBrace }
  55. () { startLayout }
  56. }
  57. <empty_layout> () { emptyLayout }
  58. {
  59. alexEOF :: Alex Token
  60. alexEOF = do
  61. (AlexPn _ l c, _, _, _) <- alexGetInput
  62. pure $ Token TokEof l c
  63. yield k (AlexPn _ l c, _, s, _) i = pure (Token (k $! (T.decodeUtf8 (Lbs.toStrict (Lbs.take i s)))) l c)
  64. always :: TokenClass -> AlexInput -> Int64 -> Alex Token
  65. always k x i = yield (const k) x i
  66. data AlexUserState = AlexUserState { layoutColumns :: [Int], startCodes :: [Int], leastColumn :: Int }
  67. alexInitUserState = AlexUserState [1] [] 0
  68. just :: Alex a -> AlexAction Token
  69. just k _ _ = k *> alexMonadScan
  70. getUserState :: Alex AlexUserState
  71. getUserState = Alex $ \s -> Right (s, alex_ust s)
  72. mapUserState :: (AlexUserState -> AlexUserState) -> Alex ()
  73. mapUserState k = Alex $ \s -> Right (s { alex_ust = k $! alex_ust s }, ())
  74. pushStartCode :: Int -> Alex ()
  75. pushStartCode c = do
  76. sc <- alexGetStartCode
  77. mapUserState $ \s -> s { startCodes = sc:startCodes s }
  78. alexSetStartCode c
  79. popStartCode :: Alex ()
  80. popStartCode = do
  81. sc <- startCodes <$> getUserState
  82. case sc of
  83. [] -> alexSetStartCode 0
  84. (x:xs) -> do
  85. mapUserState $ \s -> s { startCodes = xs }
  86. alexSetStartCode x
  87. offsideRule :: AlexInput -> Int64 -> Alex Token
  88. offsideRule (AlexPn _ line col, _, _, _) _
  89. -- | Lbs.null s = pure (Token TokEof line col)
  90. | otherwise = do
  91. ~(col':ctx) <- layoutColumns <$> getUserState
  92. case col `compare` col' of
  93. EQ -> do
  94. popStartCode
  95. pure (Token TokSemi line col)
  96. GT -> do
  97. popStartCode
  98. alexMonadScan
  99. LT -> do
  100. mapUserState $ \s -> s { layoutColumns = ctx }
  101. pure (Token TokLEnd line col)
  102. emptyLayout :: AlexInput -> Int64 -> Alex Token
  103. emptyLayout (AlexPn _ line col, _, _, _) _ = do
  104. popStartCode
  105. pushStartCode newline
  106. pure (Token TokLEnd line col)
  107. startLayout :: AlexInput -> Int64 -> Alex Token
  108. startLayout (AlexPn _ line col, _, _, _) _ = do
  109. popStartCode
  110. ~(col':_) <- layoutColumns <$> getUserState
  111. if col' >= col
  112. then pushStartCode empty_layout
  113. else mapUserState $ \s -> s { layoutColumns = col:layoutColumns s }
  114. pure (Token TokLStart line col)
  115. openBrace :: AlexInput -> Int64 -> Alex Token
  116. openBrace (AlexPn _ line col, _, _, _) _ = do
  117. popStartCode
  118. mapUserState $ \s -> s { layoutColumns = minBound:layoutColumns s }
  119. pure (Token TokOBrace line col)
  120. closeBrace :: AlexInput -> Int64 -> Alex Token
  121. closeBrace (AlexPn _ line col, _, _, _) _ = do
  122. ~(col':tail) <- layoutColumns <$> getUserState
  123. if col' < 0
  124. then mapUserState $ \s -> s { layoutColumns = tail }
  125. else pure ()
  126. pure (Token TokCBrace line col)
  127. variableOrKeyword :: AlexAction Token
  128. variableOrKeyword (AlexPn _ l c, _, s, _) size =
  129. let text = T.decodeUtf8 (Lbs.toStrict (Lbs.take size s)) in
  130. case T.unpack text of
  131. "as" -> pure (Token TokAs l c)
  132. "in" -> pure (Token TokIn l c)
  133. "data" -> pure (Token TokData l c)
  134. "postulate" -> laidOut TokPostulate l c
  135. "let" -> laidOut TokLet l c
  136. "where" -> laidOut TokWhere l c
  137. "case" -> laidOut TokCase l c
  138. _ -> pure (Token (TokVar text) l c)
  139. laidOut x l c = do
  140. pushStartCode layout
  141. mapUserState $ \s -> s { leastColumn = c }
  142. pure (Token x l c)
  143. }