diff options
author | Camil Staps | 2017-07-30 00:51:48 +0200 |
---|---|---|
committer | Camil Staps | 2017-07-30 00:54:02 +0200 |
commit | 05a47988d9466b827f7dbab44bab33a67228efe9 (patch) | |
tree | c9f2ce96dec969f1d756e25357dbbe2c79dfbad2 /Sil/Util | |
parent | Cleanup; add <> < > <= >= (diff) |
Start with positional errors (see #5)
Diffstat (limited to 'Sil/Util')
-rw-r--r-- | Sil/Util/Parser.dcl | 23 | ||||
-rw-r--r-- | Sil/Util/Parser.icl | 72 | ||||
-rw-r--r-- | Sil/Util/Printer.dcl | 4 | ||||
-rw-r--r-- | Sil/Util/Printer.icl | 4 |
4 files changed, 77 insertions, 26 deletions
diff --git a/Sil/Util/Parser.dcl b/Sil/Util/Parser.dcl index 65b050e..8474b78 100644 --- a/Sil/Util/Parser.dcl +++ b/Sil/Util/Parser.dcl @@ -6,10 +6,26 @@ from Control.Applicative import class Applicative, class Alternative from Control.Monad import class Monad from Data.Error import :: MaybeError from Data.Functor import class Functor +from Data.Maybe import :: Maybe -from Sil.Parse import :: Error +from Sil.Error import :: Error -:: Parser a b = Parser ([a] -> (MaybeError Error b, [a])) +:: Positioned a = + { pos_line :: Int + , pos_val :: a + } + +fromPositioned :: (Positioned a) -> a + +:: ParseState a + +:: ParseInput a + = PI_NewLine + | PI_Token a + +makeParseState :: [ParseInput a] -> ParseState a + +:: Parser a b = Parser ((ParseState a) -> (MaybeError Error b, ParseState a)) instance Functor (Parser a) instance Applicative (Parser a) @@ -19,7 +35,8 @@ instance Alternative (Parser a) class name a :: a -> String instance name String -runParser :: (Parser a b) [a] -> (MaybeError Error b, [a]) +runParser :: (Parser a b) (ParseState a) -> (MaybeError Error b, ParseState a) +getPositioner :: Parser a (b -> Positioned b) (<?>) :: (Parser a b) Error -> Parser a b fail :: Parser a b top :: Parser a a diff --git a/Sil/Util/Parser.icl b/Sil/Util/Parser.icl index d13bc09..34cf057 100644 --- a/Sil/Util/Parser.icl +++ b/Sil/Util/Parser.icl @@ -9,34 +9,62 @@ import Data.Error from Data.Func import $ import Data.Functor import Data.List +import Data.Maybe import Sil.Error +fromPositioned :: (Positioned a) -> a +fromPositioned p = p.pos_val + +:: ParseState a = + { ps_line :: Int + , ps_input :: [ParseInput a] + , ps_read :: [ParseInput a] + } + +makeParseState :: [ParseInput a] -> ParseState a +makeParseState i = {ps_line=1, ps_input=i, ps_read=[]} + +nextToken :: (ParseState a) -> (Maybe a, ParseState a) +nextToken ps = case ps.ps_input of + [] -> (Nothing, ps) + [PI_Token t:i] -> (Just t, {ps & ps_read=[PI_Token t:ps.ps_read], ps_input=i}) + [PI_NewLine:i] -> nextToken {ps & ps_line=ps.ps_line + 1, ps_read=[PI_NewLine:ps.ps_read], ps_input=i} + +tokenBack :: (ParseState a) -> ParseState a +tokenBack ps = case ps.ps_read of + [] -> ps + [PI_Token t:r] -> {ps & ps_read=r, ps_input=[PI_Token t:ps.ps_input]} + [PI_NewLine:r] -> tokenBack {ps & ps_read=r, ps_input=[PI_NewLine:ps.ps_input], ps_line=ps.ps_line-1} + instance Functor (Parser a) where fmap f m = liftM f m instance Applicative (Parser a) where - pure a = Parser \i -> (Ok a, i) + pure a = Parser \st -> (Ok a, st) (<*>) sf p = ap sf p instance Monad (Parser a) where - bind p f = Parser \i -> case runParser p i of + bind p f = Parser \st -> case runParser p st of (Ok r, rest) -> runParser (f r) rest - (Error e, _) -> (Error e, i) + (Error e, _) -> (Error e, st) instance Alternative (Parser a) where - empty = Parser \i -> (Error $ UnknownError "empty in Parser", i) - (<|>) p1 p2 = Parser \i -> case runParser p1 i of + empty = Parser \st -> (Error $ UnknownError "empty in Parser", st) + (<|>) p1 p2 = Parser \st -> case runParser p1 st of (Ok r, rest) -> (Ok r, rest) - (Error e1, rest) -> case runParser p2 i of - (Error e2, rest) -> (Error e2, i) + (Error e1, rest) -> case runParser p2 st of + (Error e2, rest) -> (Error e2, st) (Ok r, rest) -> (Ok r, rest) instance name String where name s = s -runParser :: (Parser a b) [a] -> (MaybeError Error b, [a]) +runParser :: (Parser a b) (ParseState a) -> (MaybeError Error b, ParseState a) runParser (Parser f) i = f i +getPositioner :: Parser a (b -> Positioned b) +getPositioner = Parser \st -> (Ok \x -> {pos_line=st.ps_line, pos_val=x}, st) + (<?>) :: (Parser a b) Error -> Parser a b (<?>) p e = Parser \i -> case runParser p i of (Error _, rest) -> (Error e, rest) @@ -46,14 +74,14 @@ fail :: Parser a b fail = empty top :: Parser a a -top = Parser \i -> case i of - [] = (Error $ UnknownError "top in Parser failed", []) - [x:xs] = (Ok x, xs) +top = Parser \st -> case nextToken st of + (Nothing, st) -> (Error $ UnknownError "top in Parser failed", st) + (Just x, st) -> (Ok x, st) peek :: Parser a a -peek = Parser \i -> case i of - [] = (Error $ UnknownError "peek in Parser failed", []) - [x:xs] = (Ok x, [x:xs]) +peek = Parser \st -> case nextToken st of + (Nothing, st) -> (Error $ UnknownError "peek in Parser failed", st) + (Just x, st) -> (Ok x, tokenBack st) satisfy :: (a -> Bool) -> Parser a a satisfy f = top >>= \r -> if (f r) (pure r) fail @@ -65,15 +93,15 @@ check f = peek >>= \r -> if (f r) (pure r) fail (until) p guard = try $ until` p guard [] where until` :: (Parser a b) (Parser a c) [b] -> Parser a [b] - until` p guard acc = Parser \i -> case runParser guard i of + until` p guard acc = Parser \st -> case runParser guard st of (Ok _, rest) -> (Ok acc, rest) - (Error _, _) -> case runParser p i of + (Error _, _) -> case runParser p st of (Ok r, rest) -> runParser (until` p guard [r:acc]) rest - (Error e, _) -> (Error e, i) + (Error e, _) -> (Error e, st) try :: (Parser a b) -> Parser a b - try p = Parser \i -> case runParser p i of - (Error e, _) -> (Error e, i) + try p = Parser \st -> case runParser p st of + (Error e, _) -> (Error e, st) (Ok r, rest) -> (Ok r, rest) item :: a -> Parser a a | ==, name a @@ -88,6 +116,6 @@ seplist sep p = liftM2 (\es e-> es ++ [e]) (some (p <* item sep)) p <|> pure empty eof :: Parser a () -eof = Parser \i -> case i of - [] = (Ok (), []) - _ = (Error $ P_Expected "eof", i) +eof = Parser \st -> case nextToken st of + (Nothing, st) -> (Ok (), st) + (_, st) -> (Error $ P_Expected "eof", st) diff --git a/Sil/Util/Printer.dcl b/Sil/Util/Printer.dcl index 5535dc2..56ad103 100644 --- a/Sil/Util/Printer.dcl +++ b/Sil/Util/Printer.dcl @@ -3,7 +3,7 @@ definition module Sil.Util.Printer from StdOverloaded import class toString, class zero from Sil.Parse import :: Token -from Sil.Syntax import :: Program, :: Function, :: CodeBlock, +from Sil.Syntax import :: Positioned, :: Program, :: Function, :: CodeBlock, :: Initialisation, :: Statement :: PrintState @@ -13,6 +13,8 @@ instance zero PrintState class PrettyPrinter t where print :: PrintState t -> String +instance PrettyPrinter String +instance PrettyPrinter (Positioned a) | PrettyPrinter a instance PrettyPrinter [Token] instance PrettyPrinter Program instance PrettyPrinter Function diff --git a/Sil/Util/Printer.icl b/Sil/Util/Printer.icl index 979e478..2a028b6 100644 --- a/Sil/Util/Printer.icl +++ b/Sil/Util/Printer.icl @@ -16,6 +16,7 @@ import Text import Sil.Parse import Sil.Syntax import Sil.Types +import Sil.Util.Parser :: PrintState = { indent :: Int @@ -33,6 +34,9 @@ instance toString PrintState where toString st = {'\t' \\ _ <- [1..st.indent]} instance PrettyPrinter String where print _ s = s +instance PrettyPrinter (Positioned a) | PrettyPrinter a +where print st p = print st $ fromPositioned p + instance PrettyPrinter [Token] where print st [] = "" |