]> Git — Sourcephile - haskell/symantic-parser.git/blob - src/Symantic/Parser/Grammar/View.hs
more on failures
[haskell/symantic-parser.git] / src / Symantic / Parser / Grammar / View.hs
1 module Symantic.Parser.Grammar.View where
2
3 import Data.Bool (Bool)
4 import Data.Eq (Eq(..))
5 import Data.Function (($), (.), id, on)
6 import Data.Ord (Ord(..))
7 import Data.Semigroup (Semigroup(..))
8 import Data.String (String)
9 import Data.Tuple (fst)
10 import Text.Show (Show(..))
11 import qualified Control.Applicative as Fct
12 import qualified Data.Functor as Functor
13 import qualified Data.HashMap.Strict as HM
14 import qualified Data.List as List
15 import qualified Data.Tree as Tree
16
17 import Symantic.Univariant.Letable
18 import Symantic.Parser.Grammar.Combinators
19
20 -- * Type 'ViewGrammar'
21 newtype ViewGrammar (showName::Bool) a = ViewGrammar { unViewGrammar ::
22 Tree.Tree (String, String) }
23
24 viewGrammar :: ViewGrammar sN a -> ViewGrammar sN a
25 viewGrammar = id
26
27 instance Show (ViewGrammar sN a) where
28 show = List.unlines . draw . unViewGrammar
29 where
30 draw :: Tree.Tree (String, String) -> [String]
31 draw (Tree.Node (x, n) ts0) =
32 (List.zipWith (<>) (List.lines x) (n : List.repeat "")) <>
33 (drawTrees ts0)
34 drawTrees [] = []
35 drawTrees [t] = shift "` " " " (draw t)
36 drawTrees (t:ts) = shift "+ " "| " (draw t) <> drawTrees ts
37 shift ind0 ind = List.zipWith (<>) (ind0 : List.repeat ind)
38
39 instance CombAlternable (ViewGrammar sN) where
40 empty = ViewGrammar $ Tree.Node ("empty", "") []
41 alt exn x y = ViewGrammar $ Tree.Node
42 ("<|>" <> if exn == ExceptionFailure then "" else ("^"<>show exn), "")
43 [unViewGrammar x, unViewGrammar y]
44 throw exn = ViewGrammar $ Tree.Node ("throw "<>show exn, "") []
45 failure _sf = ViewGrammar $ Tree.Node ("failure", "") []
46 try x = ViewGrammar $ Tree.Node ("try", "") [unViewGrammar x]
47 instance CombApplicable (ViewGrammar sN) where
48 _f <$> x = ViewGrammar $ Tree.Node ("<$>", "") [unViewGrammar x]
49 pure a = ViewGrammar $ Tree.Node ("pure "<>showsPrec 10 a "", "") []
50 x <*> y = ViewGrammar $ Tree.Node ("<*>", "") [unViewGrammar x, unViewGrammar y]
51 x <* y = ViewGrammar $ Tree.Node ("<*", "") [unViewGrammar x, unViewGrammar y]
52 x *> y = ViewGrammar $ Tree.Node ("*>", "") [unViewGrammar x, unViewGrammar y]
53 instance CombFoldable (ViewGrammar sN) where
54 chainPre f x = ViewGrammar $ Tree.Node ("chainPre", "") [unViewGrammar f, unViewGrammar x]
55 chainPost x f = ViewGrammar $ Tree.Node ("chainPost", "") [unViewGrammar x, unViewGrammar f]
56 instance
57 ShowLetName sN letName =>
58 Letable letName (ViewGrammar sN) where
59 shareable name x = ViewGrammar $
60 Tree.Node ("shareable", " "<>showLetName @sN name) [unViewGrammar x]
61 ref isRec name = ViewGrammar $
62 Tree.Node
63 ( if isRec then "rec" else "ref"
64 , " "<>showLetName @sN name
65 ) []
66 instance
67 ShowLetName sN letName =>
68 Letsable letName (ViewGrammar sN) where
69 lets defs x = ViewGrammar $
70 Tree.Node ("lets", "") $
71 (<> [unViewGrammar x]) $
72 List.sortBy (compare `on` (((fst Functor.<$>) Functor.<$>) . Tree.levels)) $
73 HM.foldrWithKey'
74 (\name (SomeLet val) ->
75 (Tree.Node ("let", " "<>showLetName @sN name) [unViewGrammar val] :))
76 [] defs
77 instance CombLookable (ViewGrammar sN) where
78 look x = ViewGrammar $ Tree.Node ("look", "") [unViewGrammar x]
79 negLook x = ViewGrammar $ Tree.Node ("negLook", "") [unViewGrammar x]
80 eof = ViewGrammar $ Tree.Node ("eof", "") []
81 instance CombMatchable (ViewGrammar sN) where
82 conditional a _ps bs b = ViewGrammar $ Tree.Node ("conditional", "")
83 [ unViewGrammar a
84 , Tree.Node ("branches", "") (unViewGrammar Fct.<$> bs)
85 , unViewGrammar b
86 ]
87 instance CombSatisfiable tok (ViewGrammar sN) where
88 satisfyOrFail _fs _p = ViewGrammar $ Tree.Node ("satisfy", "") []
89 instance CombSelectable (ViewGrammar sN) where
90 branch lr l r = ViewGrammar $ Tree.Node ("branch", "")
91 [ unViewGrammar lr, unViewGrammar l, unViewGrammar r ]