{- Copyright 2010 Dominique Devriese This file is part of the grammar-combinators library. The grammar-combinators library is free software: you can redistribute it and/or modify it under the terms of the GNU Lesser General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. Foobar is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser General Public License for more details. You should have received a copy of the GNU Lesser General Public License along with Foobar. If not, see . -} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} -- | UUParse compatibility module. module Text.GrammarCombinators.Parser.UUParse ( parseUU, parseUUR, parseUURule, parseUUE ) where import Text.GrammarCombinators.Base import Text.GrammarCombinators.Transform.UnfoldRecursion import Text.GrammarCombinators.Transform.UnfoldLoops import Text.ParserCombinators.UU hiding (Token) import Data.Enumerable (enumerate) -- We just count tokens for now (not lines and colums with handling here for newlines etc), -- locations cannot be used atm anyway... instance IsLocationUpdatedBy Int t where advance p _ = p + 1 newtype WrapP t v = WP { unWP :: P (Str (ConcreteToken t) Int) v } instance (Token t) => ProductionRule (WrapP t) where a >>> b = WP $ unWP a <*> unWP b a ||| b = WP $ unWP a <|> unWP b endOfInput = WP $ const () <$> pEnd die = WP empty instance (Token t) => EpsProductionRule (WrapP t) where epsilon v = WP $ pure v instance (Token t) => LiftableProductionRule (WrapP t) where epsilonL v _ = epsilon v instance (Token t) => TokenProductionRule (WrapP t) t where token tt = let sat :: ConcreteToken t -> Bool sat t = classify t == tt in WP $ pSym (sat, show tt, head $ enumConcreteTokens tt) anyToken = WP $ pSym (const True :: ConcreteToken t -> Bool, "anyToken", head $ enumConcreteTokens (head enumerate :: t)) -- | Parse a given string according to a given regular grammar, starting from a given -- start symbol using the UUParse error-correcting parsing library (always -- produces a result) parseUUR :: forall phi t r ix. (Token t) => ProcessingRegularGrammar phi t r -> phi ix -> [ConcreteToken t] -> r ix parseUUR gram idx = parseUURule $ gram idx -- | Parse a given string according to a given grammar, starting from a given -- start symbol using the UUParse error-correcting parsing library (always -- produces a result) parseUU :: forall phi t r ix. (Token t) => ProcessingContextFreeGrammar phi t r -> phi ix -> [ConcreteToken t] -> r ix parseUU gram = parseUUR (unfoldRecursion gram) -- | Parse a given string according to a given regular production rule using the -- UUParse error-correcting parsing library (always produces a result). parseUURule :: forall phi t r v. (Token t) => RegularRule phi r t v -> [ConcreteToken t] -> v parseUURule rule s = parse (unWP rule <* pEnd) $ listToStr s 0 -- | Parse a given string according to a given extended grammar, starting from a given -- start symbol using the UUParse error-correcting parsing library (always -- produces a result) parseUUE :: forall phi t r ix. (Token t) => ProcessingExtendedContextFreeGrammar phi t r -> phi ix -> [ConcreteToken t] -> r ix parseUUE gram = parseUU (unfoldLoops gram)