]> Git — Sourcephile - haskell/symantic-parser.git/blob - src/Symantic/Parser/Automaton.hs
add farthest position heuristic for parsing error messages
[haskell/symantic-parser.git] / src / Symantic / Parser / Automaton.hs
1 {-# LANGUAGE TemplateHaskell #-}
2 module Symantic.Parser.Automaton
3 ( module Symantic.Parser.Automaton
4 , module Symantic.Parser.Automaton.Instructions
5 , module Symantic.Parser.Automaton.Dump
6 , module Symantic.Parser.Automaton.Eval
7 , module Symantic.Parser.Automaton.Input
8 ) where
9 import Symantic.Parser.Automaton.Instructions
10 import Symantic.Parser.Automaton.Dump
11 import Symantic.Parser.Automaton.Eval
12 import Data.Either (Either(..))
13
14 import Data.Function ((.))
15 -- import Data.Char (Char)
16 import Data.Ord (Ord)
17 import Language.Haskell.TH (CodeQ)
18 import Symantic.Parser.Automaton.Input
19 import Symantic.Parser.Grammar
20 import Text.Show (Show)
21 import qualified Language.Haskell.TH.Syntax as TH
22
23 type Parser inp =
24 ObserveSharing TH.Name
25 (OptimizeComb TH.Name
26 (Automaton (inp)))
27
28 automaton :: forall inp repr a.
29 Ord (InputToken inp) =>
30 Show (InputToken inp) =>
31 TH.Lift (InputToken inp) =>
32 -- InputToken inp ~ Char =>
33 Executable repr =>
34 Readable repr (InputToken inp) =>
35 Grammar (Automaton inp) =>
36 Parser inp a ->
37 repr inp '[] ('Succ 'Zero) a
38 automaton = runAutomaton . optimizeComb . observeSharing
39
40 runParser :: forall inp a.
41 Ord (InputToken inp) =>
42 Show (InputToken inp) =>
43 TH.Lift (InputToken inp) =>
44 -- InputToken inp ~ Char =>
45 Input inp =>
46 Readable Eval (InputToken inp) =>
47 Parser inp a ->
48 CodeQ (inp -> Either (ParsingError inp) a)
49 runParser p = [|| \input -> $$(eval [||input||] (automaton p)) ||]