1 {-# LANGUAGE OverloadedStrings #-}
 
   2 module Symantic.Parser.Grammar.View where
 
   4 import Data.Bool (Bool)
 
   5 import Data.Eq (Eq(..))
 
   6 import Data.Function (($), (.), id, on)
 
   7 import Data.Ord (Ord(..))
 
   8 import Data.Semigroup (Semigroup(..))
 
   9 import Data.String (String)
 
  10 import Data.Tuple (fst)
 
  11 import Text.Show (Show(..))
 
  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
 
  17 import Symantic.ObserveSharing
 
  18 import Symantic.Optimize (normalOrderReduction)
 
  19 import Symantic.Parser.Grammar.Combinators
 
  20 import Symantic.Parser.Grammar.ObserveSharing
 
  21 import qualified Symantic.Parser.Grammar.Production as Prod
 
  23 -- * Type 'ViewGrammar'
 
  24 newtype ViewGrammar (showName::Bool) a = ViewGrammar { unViewGrammar ::
 
  25   Tree.Tree (String, String) }
 
  27 viewGrammar :: ViewGrammar sN a -> ViewGrammar sN a
 
  30 showProduction :: Prod.Production a -> String
 
  31 showProduction p = showsPrec 10 (normalOrderReduction (Prod.prodCode p)) ""
 
  33 instance Show (ViewGrammar sN a) where
 
  34   show = List.unlines . draw . unViewGrammar
 
  36     draw :: Tree.Tree (String, String) -> [String]
 
  37     draw (Tree.Node (x, n) ts0) =
 
  38       (List.zipWith (<>) (List.lines x) (n : List.repeat "")) <>
 
  41     drawTrees [t] = shift "` " "  " (draw t)
 
  42     drawTrees (t:ts) = shift "+ " "| " (draw t) <> drawTrees ts
 
  43     shift ind0 ind = List.zipWith (<>) (ind0 : List.repeat ind)
 
  45 instance CombAlternable (ViewGrammar sN) where
 
  46   empty = ViewGrammar $ Tree.Node ("empty", "") []
 
  47   alt exn x y = ViewGrammar $ Tree.Node
 
  48     ("<|>" <> if exn == ExceptionFailure then "" else ("^"<>show exn), "")
 
  49     [unViewGrammar x, unViewGrammar y]
 
  50   throw exn = ViewGrammar $ Tree.Node ("throw "<>show exn, "") []
 
  51   failure _sf = ViewGrammar $ Tree.Node ("failure", "") []
 
  52   try x = ViewGrammar $ Tree.Node ("try", "") [unViewGrammar x]
 
  53 instance CombApplicable (ViewGrammar sN) where
 
  54   _f <$> x = ViewGrammar $ Tree.Node ("<$>", "") [unViewGrammar x]
 
  55   pure a = ViewGrammar $ Tree.Node ("pure "<>showProduction a, "") []
 
  56   x <*> y = ViewGrammar $ Tree.Node ("<*>", "") [unViewGrammar x, unViewGrammar y]
 
  57   x <* y = ViewGrammar $ Tree.Node ("<*", "") [unViewGrammar x, unViewGrammar y]
 
  58   x *> y = ViewGrammar $ Tree.Node ("*>", "") [unViewGrammar x, unViewGrammar y]
 
  59 instance CombFoldable (ViewGrammar sN) where
 
  60   chainPre f x = ViewGrammar $ Tree.Node ("chainPre", "") [unViewGrammar f, unViewGrammar x]
 
  61   chainPost x f = ViewGrammar $ Tree.Node ("chainPost", "") [unViewGrammar x, unViewGrammar f]
 
  63   ShowLetName sN letName =>
 
  64   Referenceable letName (ViewGrammar sN) where
 
  65   ref isRec name = ViewGrammar $
 
  67       ( if isRec then "rec" else "ref"
 
  68       , " "<>showLetName @sN name
 
  71   ShowLetName sN letName =>
 
  72   Letsable letName (ViewGrammar sN) where
 
  73   lets defs x = ViewGrammar $
 
  74     Tree.Node ("lets", "") $
 
  75       (<> [unViewGrammar x]) $
 
  76       List.sortBy (compare `on` (((fst Functor.<$>) Functor.<$>) . Tree.levels)) $
 
  78         (\name (SomeLet val) ->
 
  79           (Tree.Node ("let", " "<>showLetName @sN name) [unViewGrammar val] :))
 
  81 instance CombLookable (ViewGrammar sN) where
 
  82   look x = ViewGrammar $ Tree.Node ("look", "") [unViewGrammar x]
 
  83   negLook x = ViewGrammar $ Tree.Node ("negLook", "") [unViewGrammar x]
 
  84   eof = ViewGrammar $ Tree.Node ("eof", "") []
 
  85 instance CombMatchable (ViewGrammar sN) where
 
  86   conditional a bs d = ViewGrammar $ Tree.Node ("conditional", "")
 
  87     $ Tree.Node ("condition", "") [unViewGrammar a]
 
  88     : Tree.Node ("default", "") [unViewGrammar d]
 
  89     : ((\(p,b) -> Tree.Node ("branch "<>showProduction p, "") [unViewGrammar b]) Functor.<$> bs)
 
  90 instance CombSatisfiable tok (ViewGrammar sN) where
 
  91   satisfyOrFail _fs p = ViewGrammar $ Tree.Node
 
  92     ("satisfy "<>showProduction p, "") []
 
  93 instance CombSelectable (ViewGrammar sN) where
 
  94   branch lr l r = ViewGrammar $ Tree.Node ("branch", "")
 
  95     [ unViewGrammar lr, unViewGrammar l, unViewGrammar r ]
 
  96 instance CombRegisterableUnscoped (ViewGrammar sN) where
 
  97   newUnscoped r x y = ViewGrammar $ Tree.Node ("new "<>show r, "") [ unViewGrammar x,  unViewGrammar y ]
 
  98   getUnscoped r = ViewGrammar $ Tree.Node ("get "<>show r, "") [ ]
 
  99   putUnscoped r x = ViewGrammar $ Tree.Node ("put "<>show r, "") [ unViewGrammar x ]