]> Git — Sourcephile - haskell/symantic.git/blob - symantic-grammar/Language/Symantic/Grammar/Regular.hs
Split into symantic{,-grammar,-lib}.
[haskell/symantic.git] / symantic-grammar / Language / Symantic / Grammar / Regular.hs
1 -- | This module defines symantics
2 -- for regular grammars.
3 module Language.Symantic.Grammar.Regular where
4
5 import Data.String (IsString(..))
6 import qualified Data.Text as Text
7 import Data.Semigroup (Semigroup(..))
8
9 import Language.Symantic.Grammar.EBNF
10 import Language.Symantic.Grammar.Terminal
11
12 -- * Type 'Reg'
13 -- | Left or right regular grammar.
14 newtype Reg (lr::LR) g a = Reg { unReg :: g a }
15 deriving (IsString, Functor, Gram_Terminal)
16 deriving instance Alter g => Alter (Reg lr g)
17 deriving instance Gram_Rule g => Gram_Rule (Reg lr g)
18 deriving instance (Functor g, Alter g, Gram_RegL g) => Gram_RegL (RegL g)
19 deriving instance (Functor g, Alter g, Gram_RegR g) => Gram_RegR (RegR g)
20 deriving instance Gram_RegL RuleDef
21 deriving instance Gram_RegR RuleDef
22 deriving instance Gram_RuleDef g => Gram_RuleDef (RegR g)
23 deriving instance Gram_RuleDef g => Gram_RuleDef (RegL g)
24
25 reg_of_Terminal :: Terminal g a -> Reg lr g a
26 reg_of_Terminal (Terminal g) = Reg g
27
28 type RegL = Reg 'L
29 type RegR = Reg 'R
30
31 -- ** Class 'Alter'
32 -- | Like 'Alternative' but without the 'Applicative' super-class,
33 -- because a regular grammar is not closed under 'Applicative'.
34 -- And also because the alternative operator has to backtrack
35 -- when the first alternative fails.
36 class Alter g where
37 empty :: g a
38 (<+>) :: g a -> g a -> g a
39 infixl 3 <+>
40 choice :: [g a] -> g a
41 choice = foldr (<+>) empty
42 deriving instance Alter p => Alter (Terminal p)
43 deriving instance Alter RuleDef
44 instance Alter EBNF where
45 empty = ebnf_const $ "\"\""
46 EBNF g <+> EBNF q = EBNF $ \bo po -> infix_paren po op $
47 g bo (op, L) <> " | " <> q bo (op, R)
48 where op = infixB L 2
49 choice [] = empty
50 choice [g] = g
51 choice l@(_:_) = EBNF $ \bo po -> infix_paren po op $
52 Text.intercalate " | " $
53 (unEBNF <$> l) <*> pure bo <*> pure (op, L)
54 where op = infixB L 2
55
56 -- ** Class 'Gram_RegR'
57 -- | Symantics for right regular grammars.
58 class (Functor g, Alter g) => Gram_RegR g where
59 (.*>) :: Terminal g (a -> b) -> RegR g a -> RegR g b
60 infixl 4 .*>
61 manyR :: Terminal g a -> RegR g [a]
62 manyR g = (:) <$> g .*> manyR g <+> empty
63 someR :: Terminal g a -> RegR g [a]
64 someR g = (:) <$> g .*> manyR g
65 instance Gram_RegR EBNF where
66 Terminal f .*> Reg x = Reg $ f <*> x
67 manyR (Terminal (EBNF g)) = Reg $ EBNF $ \rm _po -> "{" <> g rm (op, L) <> "}" where op = infixN0
68 someR (Terminal (EBNF g)) = Reg $ EBNF $ \rm _po -> "{" <> g rm (op, L) <> "}-" where op = infixN0
69
70 -- ** Class 'Gram_RegL'
71 -- | Symantics for left regular grammars.
72 class (Functor g, Alter g) => Gram_RegL g where
73 (<*.) :: RegL g (a -> b) -> Terminal g a -> RegL g b
74 infixl 4 <*.
75 manyL :: Terminal g a -> RegL g [a]
76 manyL g' = reverse <$> go g'
77 where go g = flip (:) <$> go g <*. g <+> empty
78 someL :: Terminal g a -> RegL g [a]
79 someL g = (\cs c -> cs ++ [c]) <$> manyL g <*. g
80 instance Gram_RegL EBNF where
81 Reg f <*. Terminal x = Reg $ f <*> x
82 manyL (Terminal (EBNF g)) = Reg $ EBNF $ \rm _po -> "{" <> g rm (op, L) <> "}" where op = infixN0
83 someL (Terminal (EBNF g)) = Reg $ EBNF $ \rm _po -> "{" <> g rm (op, L) <> "}-" where op = infixN0