1 {-# LANGUAGE OverloadedStrings #-}
2 module Symantic.Parser.Grammar.Write where
4 import Control.Monad (Monad(..))
5 import Data.Function (($))
6 import Data.Maybe (Maybe(..), fromMaybe, catMaybes)
7 import Data.Monoid (Monoid(..))
8 import Data.Semigroup (Semigroup(..))
9 import Data.String (IsString(..))
10 import Text.Show (Show(..))
11 import qualified Data.Functor as Pre
12 import qualified Data.List as List
13 import qualified Data.Text.Lazy as TL
14 import qualified Data.Text.Lazy.Builder as TLB
16 import Symantic.Univariant.Letable
17 import Symantic.Parser.Grammar.Combinators
18 import Symantic.Parser.Grammar.Fixity
21 newtype WriteComb a = WriteComb { unWriteComb :: WriteCombInh -> Maybe TLB.Builder }
23 instance IsString (WriteComb a) where
24 fromString s = WriteComb $ \_inh ->
25 if List.null s then Nothing
26 else Just (fromString s)
28 -- ** Type 'WriteCombInh'
31 { writeCombInh_indent :: TLB.Builder
32 , writeCombInh_op :: (Infix, Side)
33 , writeCombInh_pair :: Pair
36 emptyWriteCombInh :: WriteCombInh
37 emptyWriteCombInh = WriteCombInh
38 { writeCombInh_indent = "\n"
39 , writeCombInh_op = (infixN0, SideL)
40 , writeCombInh_pair = pairParen
43 writeComb :: WriteComb a -> TL.Text
44 writeComb (WriteComb r) = TLB.toLazyText $ fromMaybe "" $ r emptyWriteCombInh
47 Semigroup s => IsString s =>
48 WriteCombInh -> Infix -> Maybe s -> Maybe s
49 pairWriteCombInh inh op s =
50 if isPairNeeded (writeCombInh_op inh) op
51 then Just (fromString o<>" ")<>s<>Just (" "<>fromString c)
53 where (o,c) = writeCombInh_pair inh
55 instance Show letName => Letable letName WriteComb where
56 def name x = WriteComb $ \inh ->
57 pairWriteCombInh inh op $
59 <> Just (fromString (show name))
63 ref rec name = WriteComb $ \inh ->
64 pairWriteCombInh inh op $
65 Just (if rec then "rec " else "ref ") <>
66 Just (fromString (show name))
69 instance Applicable WriteComb where
70 pure _ = WriteComb $ return Nothing
72 WriteComb x <*> WriteComb y = WriteComb $ \inh ->
74 { writeCombInh_op = (op, side)
75 , writeCombInh_pair = pairParen
77 case x (inh' SideL) of
78 Nothing -> y (inh' SideR)
80 case y (inh' SideR) of
83 pairWriteCombInh inh op $
84 Just $ xt <> ", " <> yt
87 instance Alternable WriteComb where
89 try x = WriteComb $ \inh ->
90 pairWriteCombInh inh op $
91 Just "try " <> unWriteComb x inh
94 x <|> y = WriteComb $ \inh ->
95 pairWriteCombInh inh op $
97 { writeCombInh_op = (op, SideL)
98 , writeCombInh_pair = pairParen
102 { writeCombInh_op = (op, SideR)
103 , writeCombInh_pair = pairParen
105 where op = infixB SideL 3
106 instance Charable WriteComb where
108 instance Selectable WriteComb where
109 branch lr l r = WriteComb $ \inh ->
110 pairWriteCombInh inh op $
112 unWriteComb lr inh <> Just " " <>
113 unWriteComb l inh <> Just " " <>
117 instance Matchable WriteComb where
118 conditional _ps bs a d = WriteComb $ \inh ->
119 pairWriteCombInh inh op $
120 Just "conditional " <>
122 Just (mconcat (List.intersperse ", " $
123 catMaybes $ (Pre.<$> bs) $ \x ->
124 unWriteComb x inh{writeCombInh_op=(infixN 0, SideL)})) <>
126 unWriteComb a inh <> Just " " <>
130 instance Lookable WriteComb where
131 look x = WriteComb $ \inh ->
132 pairWriteCombInh inh op $
133 Just "look " <> unWriteComb x inh
135 negLook x = WriteComb $ \inh ->
136 pairWriteCombInh inh op $
137 Just "negLook " <> unWriteComb x inh
139 instance Foldable WriteComb where
140 chainPre f x = WriteComb $ \inh ->
141 pairWriteCombInh inh op $
143 unWriteComb f inh <> Just " " <>
146 chainPost f x = WriteComb $ \inh ->
147 pairWriteCombInh inh op $
149 unWriteComb f inh <> Just " " <>