{- 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 KindSignatures #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} module Text.GrammarCombinators.Utils.EnumTokens ( enumRuleTokens, enumTokens, enumAllTokens ) where import Text.GrammarCombinators.Base import Text.GrammarCombinators.Utils.IsReachable import Data.Enumerable (enumerate) newtype EnumTokensRule (phi :: * -> *) (r :: * -> *) t v = ETR { unETR :: [t] } instance ProductionRule (EnumTokensRule phi r t) where die = ETR [] endOfInput = ETR [] a ||| b = ETR $ unETR a ++ unETR b a >>> b = ETR $ unETR a ++ unETR b instance LiftableProductionRule (EnumTokensRule phi r t) where epsilonL v _ = epsilon v instance EpsProductionRule (EnumTokensRule phi r t) where epsilon _ = ETR [] instance (Token t) => TokenProductionRule (EnumTokensRule phi r t) t where token t = ETR [t] anyToken = ETR enumerate instance (ShowFam phi) => RecProductionRule (EnumTokensRule phi r t) phi r where ref _ = ETR [] instance (ShowFam phi) => LoopProductionRule (EnumTokensRule phi r t) phi r where manyRef _ = ETR [] many1Ref _ = ETR [] -- | Enumerate all tokens that can be present in any match of a given production rule. enumRuleTokens :: (Domain phi, Token t) => ExtendedContextFreeRule phi r t v -> [t] enumRuleTokens rule = unETR rule enumTokens' :: forall phi t r rr . (Token t, Domain phi) => ((forall ix. phi ix -> [t] -> [t]) -> [t] -> [t]) -> GExtendedContextFreeGrammar phi t r rr -> [t] enumTokens' fold' grammar = let addRuleTokens :: forall ix. phi ix -> [t] -> [t] addRuleTokens idx b = enumRuleTokens (grammar idx) ++ b in fold' addRuleTokens [] -- | Enumerate all tokens that can be present in any match of any string that can be matched -- by a given non-terminal in a given grammar. enumTokens :: (Token t, Domain phi) => GExtendedContextFreeGrammar phi t r rr -> phi ix -> [t] enumTokens g idx = enumTokens' (foldReachable g idx) g -- | Enumerate all tokens that can be present in any match of any string that can be matched -- by any non-terminal in a given grammar. enumAllTokens :: (Token t, Domain phi) => GExtendedContextFreeGrammar phi t r rr -> [t] enumAllTokens = enumTokens' foldFam