1 {-# LANGUAGE ConstraintKinds #-}
2 {-# OPTIONS_GHC -fno-warn-orphans #-}
3 module Parsing.Test where
5 import Control.Applicative (Applicative(..))
6 import qualified Control.Applicative as Alt
8 import qualified Data.Char as Char
9 import Data.Functor.Identity
10 import qualified Data.List as List
11 import Data.String (IsString(..))
12 import qualified Data.Text as Text
13 import Prelude hiding (any, (^), exp)
14 import qualified Text.Megaparsec as P
16 import Language.Symantic.Grammar
19 type ParsecC e s = (P.Token s ~ Char, P.Stream s, P.ErrorComponent e)
20 instance ParsecC e s => IsString (P.ParsecT e s m [Char]) where
22 instance ParsecC e s => Gram_Rule (P.ParsecT e s m) where
23 rule = P.label . Text.unpack
24 instance ParsecC e s => Gram_Terminal (P.ParsecT e s m) where
29 unicat cat = P.satisfy $ (`List.elem` cats) . Char.generalCategory
30 where cats = unicode_categories cat
31 range (l, h) = P.satisfy $ \c -> l <= c && c <= h
32 but (Terminal f) (Terminal p) = Terminal $ P.notFollowedBy (P.try p) *> f
33 instance ParsecC e s => Alter (P.ParsecT e s m) where
37 instance ParsecC e s => Try (P.ParsecT e s m) where
39 instance ParsecC e s => Gram_RegR (P.ParsecT e s m) where
40 Terminal f .*> Reg x = Reg $ f <*> x
41 instance ParsecC e s => Gram_RegL (P.ParsecT e s m) where
42 Reg f <*. Terminal x = Reg $ f <*> x
43 instance ParsecC e s => App (P.ParsecT e s m) where
45 instance ParsecC e s => Alt (P.ParsecT e s m) where
51 instance ParsecC e s => Gram_CF (P.ParsecT e s m) where
52 CF f <& Reg p = CF $ P.lookAhead f <*> p
53 Reg f &> CF p = CF $ P.lookAhead f <*> p
54 minus (CF f) (Reg p) = CF $ P.notFollowedBy (P.try p) *> f
55 instance ParsecC e s => Gram_Meta P.SourcePos (P.ParsecT e s m) where
59 instance ParsecC e s => Gram_Lexer (P.ParsecT e s m)
60 instance ParsecC e s => Gram_Op (P.ParsecT e s m)
63 => P.ParsecT P.Dec s m a -> s
64 -> m (Either (P.ParseError (P.Token s) P.Dec) a)
65 runParserT p = P.runParserT p ""
68 :: P.ParsecT P.Dec s Identity a -> s
69 -> Either (P.ParseError (P.Token s) P.Dec) a
70 runParser p = P.runParser p ""
72 elide :: String -> String
73 elide s | length s > 42 = take 42 s ++ ['…']