{-# LANGUAGE TypeOperators, FlexibleInstances #-}
module GLL.Combinators.BinaryInterface (
term_parser, satisfy,
keychar, keyword, int_lit, float_lit, bool_lit, char_lit, string_lit, alt_id_lit, id_lit, token,
char,
(<**>),
(<||>),
(<$$>),
(<:=>),(<::=>),chooses,chooses_prec,
BNF, SymbExpr, toSymb, mkRule,
Token(..), Parseable(..), SubsumesToken(..), unlexTokens, unlexToken,
grammarOf, parse, printParseData, evaluatorWithParseData,
parseWithOptions, parseWithParseOptions, printParseDataWithOptions, evaluatorWithParseDataAndOptions,printGrammarData,
CombinatorOptions, CombinatorOption,
GLL.Combinators.Options.maximumErrors, throwErrors,
maximumPivot, maximumPivotAtNt, leftBiased,
fullSPPF, allNodes, packedNodesOnly, strictBinarisation,
GLL.Parser.noSelectTest,
parseWithOptionsAndError, parseWithParseOptionsAndError,
parseResult, parseResultWithOptions,ParseResult(..),
default_lexer,
lexer, LexerSettings(..), emptyLanguage,
mkNt,
(<$$), (**>), (<**),
optional, preferably, reluctantly, optionalWithDef,
multiple, multiple1, multipleSepBy, multipleSepBy1,
multipleSepBy2, within, parens, braces, brackets, angles,
(<:=), (<::=),(<<<**>), (<**>>>), (<<**>), (<<<**), (**>>>), (<**>>),
longest_match,shortest_match,
many, many1, some, some1,
manySepBy, manySepBy1, manySepBy2,
someSepBy, someSepBy1,someSepBy2,
memo, newMemoTable, memClear, MemoTable, MemoRef, useMemoisation,
module GLL.Combinators.Interface
) where
import GLL.Combinators.Interface hiding (within, (**>), (<**>), (<**), (<<<**>), (<<<**), (**>>>), (<**>>>), satisfy, (<||>), (<||), (||>), (<$$>), (<$$), (<:=>), (<:=),(<::=>), (<::=), mkNt, manySepBy, manySepBy1, manySepBy2, multiple, multipleSepBy, many, multipleSepBy1, multipleSepBy2, someSepBy, someSepBy1, someSepBy2, some, memo, some1, many1, multiple1, shortest_match, longest_match, (<**>>), (<<**>), angles, braces, brackets, parens, within, optional, optionalWithDef, preferably, reluctantly, chooses, chooses_prec)
import qualified GLL.Combinators.Interface as IF
import GLL.Combinators.Options
import GLL.Combinators.Visit.Join
import GLL.Combinators.Visit.Sem (emptyAncestors)
import GLL.Combinators.Memoisation
import GLL.Combinators.Lexer
import GLL.Types.Grammar
import GLL.Parser hiding (parse, parseWithOptions)
import qualified GLL.Parser as GLL
import Control.Compose (OO(..))
import Control.Arrow
import qualified Data.Array as A
import qualified Data.IntMap as IM
import qualified Data.Map as M
import Data.Text (pack)
import Data.IORef
import Data.Time.Clock
import System.IO.Unsafe
infixl 2 <:=>
(<:=>) :: (Show t, Ord t) => String -> BNF t a -> BNF t a
n <:=> p = n IF.<:=> p
infixl 2 <::=>
(<::=>) :: (Show t, Ord t) => String -> BNF t a -> BNF t a
n <::=> p = n IF.<::=> p
chooses :: (Show t, Ord t) => String -> [BNF t a] -> BNF t a
chooses p alts = IF.chooses p alts
chooses_prec :: (Show t, Ord t) => String -> [BNF t a] -> BNF t a
chooses_prec p alts = IF.chooses_prec p alts
infixl 4 <$$>
(<$$>) :: (Show t, Ord t) => (a -> b) -> BNF t a -> BNF t b
f <$$> p' = IF.toSymb (f IF.<$$> p')
infixl 4 <**>,<<<**>,<**>>>
(<**>) :: (Show t, Ord t) => BNF t (a -> b) -> BNF t a -> BNF t b
pl' <**> pr' = IF.toSymb (pl' IF.<**> pr')
(<**>>>) :: (Show t, Ord t) => BNF t (a -> b) -> BNF t a -> BNF t b
pl' <**>>> pr' = IF.toSymb (pl' IF.<**>>> pr')
(<<<**>) :: (Show t, Ord t) => BNF t (a -> b) -> BNF t a -> BNF t b
pl' <<<**> pr' = IF.toSymb (pl' IF.<<<**> pr')
infixr 3 <||>
(<||>) :: (Show t, Ord t) => BNF t a -> BNF t a -> BNF t a
l' <||> r' = IF.toSymb (l' IF.<||> r')
longest_match :: (Show t, Ord t) => BNF t a -> BNF t a
longest_match isalt = IF.toSymb (IF.longest_match isalt)
shortest_match :: (Show t, Ord t) => BNF t a -> BNF t a
shortest_match isalt = IF.toSymb (IF.shortest_match isalt)
satisfy :: (Show t, Ord t ) => a -> BNF t a
satisfy a = IF.toSymb (IF.satisfy a)
memo :: (Ord t, Show t) => MemoRef [a] -> BNF t a -> BNF t a
memo ref p' = IF.memo ref p'
mkNt :: (Show t, Ord t) => BNF t a -> String -> String
mkNt p str = IF.mkNt p str
(<$$) :: (Show t, Ord t) => b -> BNF t a -> BNF t b
f <$$ p = const f <$$> p
infixl 4 <$$
infixl 4 **>, <<**>, **>>>
(**>) :: (Show t, Ord t) => BNF t a -> BNF t b -> BNF t b
l **> r = flip const <$$> l <**> r
(**>>>) :: (Show t, Ord t) => BNF t a -> BNF t b -> BNF t b
l **>>> r = flip const <$$> l <**>>> r
(<<**>) :: (Show t, Ord t) => BNF t a -> BNF t b -> BNF t b
l <<**>r = flip const <$$> l <<<**> r
infixl 4 <**, <<<**, <**>>
(<**) :: (Show t, Ord t) => BNF t a -> BNF t b -> BNF t a
l <** r = const <$$> l <**> r
(<**>>) :: (Show t, Ord t) => BNF t a -> BNF t b -> BNF t a
l <**>> r = const <$$> l <**>>> r
(<<<**) :: (Show t, Ord t) => BNF t a -> BNF t b -> BNF t a
l <<<** r = const <$$> l <<<**> r
x <::= altPs = x IF.<::= altPs
infixl 2 <::=
x <:= altPs = x IF.<:= altPs
infixl 2 <:=
many :: (Show t, Ord t) => BNF t a -> BNF t [a]
many = multiple_ (<<<**>)
many1 :: (Show t, Ord t) => BNF t a -> BNF t [a]
many1 = multiple1_ (<<<**>)
some :: (Show t, Ord t) => BNF t a -> BNF t [a]
some = multiple_ (<**>>>)
some1 :: (Show t, Ord t) => BNF t a -> BNF t [a]
some1 = multiple1_ (<**>>>)
multiple :: (Show t, Ord t) => BNF t a -> BNF t [a]
multiple = multiple_ (<**>)
multiple1 :: (Show t, Ord t) => BNF t a -> BNF t [a]
multiple1 = multiple1_ (<**>)
multiple_ disa p = let fresh = mkNt p "*"
in fresh <::=> ((:) <$$> p) `disa` (multiple_ disa p) <||> satisfy []
multiple1_ disa p = let fresh = mkNt p "+"
in fresh <::=> ((:) <$$> p) `disa` (multiple_ disa p)
manySepBy :: (Show t, Ord t) => BNF t a -> BNF t b -> BNF t [a]
manySepBy = sepBy many
manySepBy1 :: (Show t, Ord t) => BNF t a -> BNF t b -> BNF t [a]
manySepBy1 = sepBy1 many
someSepBy :: (Show t, Ord t) => BNF t a -> BNF t b -> BNF t [a]
someSepBy = sepBy some
someSepBy1 :: (Show t, Ord t) => BNF t a -> BNF t b -> BNF t [a]
someSepBy1 = sepBy1 some
multipleSepBy :: (Show t, Ord t) => BNF t a -> BNF t b -> BNF t [a]
multipleSepBy = sepBy multiple
multipleSepBy1 :: (Show t, Ord t) => BNF t a -> BNF t b -> BNF t [a]
multipleSepBy1 = sepBy1 multiple
sepBy :: (Show t, Ord t) => (BNF t a -> BNF t [a]) -> BNF t a -> BNF t b -> BNF t [a]
sepBy mult p c = mkRule $ satisfy [] <||> (:) <$$> p <**> mult (c **> p)
sepBy1 :: (Show t, Ord t) => (BNF t a -> BNF t [a]) -> BNF t a -> BNF t b -> BNF t [a]
sepBy1 mult p c = mkRule $ (:) <$$> p <**> mult (c **> p)
multipleSepBy2 p s = mkRule $
(:) <$$> p <** s <**> multipleSepBy1 p s
someSepBy2 p s = mkRule $
(:) <$$> p <** s <**> someSepBy1 p s
manySepBy2 p s = mkRule $
(:) <$$> p <** s <**> manySepBy1 p s
optional :: (Show t, Ord t) => BNF t a -> BNF t (Maybe a)
optional p = fresh
<:=> Just <$$> p
<||> satisfy Nothing
where fresh = mkNt p "?"
preferably :: (Show t, Ord t) => BNF t a -> BNF t (Maybe a)
preferably p = fresh
<:= Just <$$> p
<||> satisfy Nothing
where fresh = mkNt p "?"
reluctantly :: (Show t, Ord t) => BNF t a -> BNF t (Maybe a)
reluctantly p = fresh
<:= satisfy Nothing
<||> Just <$$> p
where fresh = mkNt p "?"
optionalWithDef :: (Show t, Ord t) => BNF t a -> a -> BNF t a
optionalWithDef p def = mkNt p "?" <:=> id <$$> p <||> satisfy def
within :: (Show t, Ord t) => BNF t a -> BNF t b -> BNF t c -> BNF t b
within l p r = IF.toSymb (l **> p <** r)
parens p = within (keychar '(') p (keychar ')')
braces p = within (keychar '{') p (keychar '}')
brackets p = within (keychar '[') p (keychar ']')
angles p = within (keychar '<') p (keychar '>')
quotes p = within (keychar '\'') p (keychar '\'')
dquotes p = within (keychar '"') p (keychar '"')