my blog lives here now
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.

140 lines
3.0 KiB

2 years ago
  1. {-# LANGUAGE LambdaCase #-}
  2. module Parser
  3. ( Parser()
  4. , module X
  5. , Parser.any
  6. , satisfy
  7. , string
  8. , digit
  9. , number
  10. , spaces
  11. , reserved
  12. , lexeme
  13. , (<?>)
  14. , runParser
  15. , between ) where
  16. import Control.Applicative as X
  17. import Control.Monad as X
  18. import Data.Char
  19. newtype Parser a
  20. = Parser { parse :: String -> Either String (a, String) }
  21. runParser :: Parser a -> String -> Either String a
  22. runParser (Parser p) s = fst <$> p s
  23. (<?>) :: Parser a -> String -> Parser a
  24. p <?> err = p <|> fail err
  25. infixl 2 <?>
  26. instance Functor Parser where
  27. fn `fmap` (Parser p) = Parser go where
  28. go st = case p st of
  29. Left e -> Left e
  30. Right (res, str') -> Right (fn res, str')
  31. instance Applicative Parser where
  32. pure x = Parser $ \str -> Right (x, str)
  33. (Parser p) <*> (Parser p') = Parser go where
  34. go st = case p st of
  35. Left e -> Left e
  36. Right (fn, st') -> case p' st' of
  37. Left e' -> Left e'
  38. Right (v, st'') -> Right (fn v, st'')
  39. instance Alternative Parser where
  40. empty = fail "nothing"
  41. (Parser p) <|> (Parser p') = Parser go where
  42. go st = case p st of
  43. Left _ -> p' st
  44. Right x -> Right x
  45. instance Monad Parser where
  46. return = pure
  47. (Parser p) >>= f = Parser go where
  48. go s = case p s of
  49. Left e -> Left e
  50. Right (x, s') -> parse (f x) s'
  51. fail m = Parser go where
  52. go = Left . go'
  53. go' [] = "expected " ++ m ++ ", got to the end of stream"
  54. go' (x:xs) = "expected " ++ m ++ ", got '" ++ x:"'"
  55. any :: Parser Char
  56. any = Parser go where
  57. go [] = Left "any: end of file"
  58. go (x:xs) = Right (x,xs)
  59. satisfy :: (Char -> Bool) -> Parser Char
  60. satisfy f = do
  61. x <- Parser.any
  62. if f x
  63. then return x
  64. else fail "a solution to the function"
  65. char :: Char -> Parser Char
  66. char c = satisfy (c ==) <?> "literal " ++ [c]
  67. oneOf :: String -> Parser Char
  68. oneOf s = satisfy (`elem` s) <?> "one of '" ++ s ++ "'"
  69. string :: String -> Parser String
  70. string [] = return []
  71. string (x:xs) = do
  72. char x
  73. string xs
  74. return $ x:xs
  75. natural :: Parser Integer
  76. natural = read <$> some (satisfy isDigit)
  77. lexeme :: Parser a -> Parser a
  78. lexeme = (<* spaces)
  79. reserved :: String -> Parser String
  80. reserved = lexeme . string
  81. spaces :: Parser String
  82. spaces = many $ oneOf " \n\r"
  83. digit :: Parser Char
  84. digit = satisfy isDigit
  85. number :: Parser Int
  86. number = do
  87. s <- string "-" <|> empty
  88. cs <- some digit
  89. return $ read (s ++ cs)
  90. between :: Parser b -> Parser c -> Parser a -> Parser a
  91. between o c x = o *> x <* c
  92. contents :: Parser a -> Parser a
  93. contents x = spaces *> x <* spaces
  94. sep :: Parser b -> Parser a -> Parser [a]
  95. sep s c = sep1 s c <|> return []
  96. sep1 :: Parser b -> Parser a -> Parser [a]
  97. sep1 s c = do
  98. x <- c
  99. xs <- many $ s >> c
  100. return $ x:xs
  101. option :: a -> Parser a -> Parser a
  102. option x p = p <|> return x
  103. optionMaybe :: Parser a -> Parser (Maybe a)
  104. optionMaybe p = option Nothing $ Just <$> p
  105. optional :: Parser a -> Parser ()
  106. optional p = void p <|> return ()
  107. eof :: Parser ()
  108. eof = Parser go where
  109. go (x:_) = Left $ "expected eof, got '" ++ x:"'"
  110. go [] = Right ((), [])