]> Git — Sourcephile - haskell/symantic.git/blob - symantic-lib/Language/Symantic/Parsing/Test.hs
Cosmetic cleanup.
[haskell/symantic.git] / symantic-lib / Language / Symantic / Parsing / Test.hs
1 {-# LANGUAGE ConstraintKinds #-}
2 {-# OPTIONS_GHC -fno-warn-orphans #-}
3 module Parsing.Test where
4
5 import Control.Applicative (Applicative(..))
6 import qualified Control.Applicative as Alt
7 import qualified Data.Char as Char
8 import qualified Data.List as List
9 import Data.String (IsString(..))
10 import qualified Data.Text as Text
11 import Prelude hiding (any, (^), exp)
12 import qualified Text.Megaparsec as P
13
14 import Language.Symantic.Grammar
15
16 -- * Type 'ParsecT'
17 type ParsecC e s = (P.Token s ~ Char, P.Stream s, P.ErrorComponent e)
18 instance ParsecC e s => IsString (P.ParsecT e s m [Char]) where
19 fromString = P.string
20 instance ParsecC e s => Gram_Rule (P.ParsecT e s m) where
21 rule = P.label . Text.unpack
22 instance ParsecC e s => Gram_Terminal (P.ParsecT e s m) where
23 any = P.anyChar
24 eoi = P.eof
25 char = P.char
26 string = P.string
27 unicat cat = P.satisfy $ (`List.elem` cats) . Char.generalCategory
28 where cats = unicode_categories cat
29 range (l, h) = P.satisfy $ \c -> l <= c && c <= h
30 Terminal f `but` Terminal p = Terminal $ P.notFollowedBy (P.try p) *> f
31 instance ParsecC e s => Alter (P.ParsecT e s m) where
32 empty = Alt.empty
33 (<+>) = (Alt.<|>)
34 choice = P.choice
35 instance ParsecC e s => Try (P.ParsecT e s m) where
36 try = P.try
37 instance ParsecC e s => Gram_RegR (P.ParsecT e s m) where
38 Terminal f .*> Reg x = Reg $ f <*> x
39 instance ParsecC e s => Gram_RegL (P.ParsecT e s m) where
40 Reg f <*. Terminal x = Reg $ f <*> x
41 instance ParsecC e s => App (P.ParsecT e s m) where
42 between = P.between
43 instance ParsecC e s => Alt (P.ParsecT e s m) where
44 option = P.option
45 optional = P.optional
46 many = P.many
47 some = P.some
48 skipMany = P.skipMany
49 instance ParsecC e s => Gram_CF (P.ParsecT e s m) where
50 CF f <& Reg p = CF $ P.lookAhead f <*> p
51 Reg f &> CF p = CF $ P.lookAhead f <*> p
52 minus (CF f) (Reg p) = CF $ P.notFollowedBy (P.try p) *> f
53 instance ParsecC e s => Gram_Meta P.SourcePos (P.ParsecT e s m) where
54 metaG p = do
55 pos <- P.getPosition
56 ($ pos) <$> p
57 instance ParsecC e s => Gram_Lexer (P.ParsecT e s m)
58 instance ParsecC e s => Gram_Op (P.ParsecT e s m)