{- 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.Transform.FilterDies ( filterDies, filterDiesP, filterDiesE, filterDiesPE, filterDiesLE ) where import Text.GrammarCombinators.Base data FilterDiesRule p (phi :: * -> *) (r :: * -> *) t v = FDBaseRule (p v) | FDDieRule instance ProductionRule p => ProductionRule (FilterDiesRule p phi r t) where endOfInput = FDBaseRule endOfInput FDDieRule >>> _ = FDDieRule _ >>> FDDieRule = FDDieRule (FDBaseRule ra) >>> (FDBaseRule rb) = FDBaseRule $ ra >>> rb FDDieRule ||| rb = rb (FDBaseRule ra) ||| fdrb = FDBaseRule $ case fdrb of FDDieRule -> ra (FDBaseRule rb) -> ra ||| rb die = FDDieRule instance (EpsProductionRule p) => EpsProductionRule (FilterDiesRule p phi r t) where epsilon = FDBaseRule . epsilon instance (LiftableProductionRule p) => LiftableProductionRule (FilterDiesRule p phi r t) where epsilonL v q = FDBaseRule $ epsilonL v q instance (TokenProductionRule p t) => TokenProductionRule (FilterDiesRule p phi r t) t where token = FDBaseRule . token anyToken = FDBaseRule anyToken instance (RecProductionRule p phi r) => RecProductionRule (FilterDiesRule p phi r t) phi r where ref = FDBaseRule . ref instance (PenaltyProductionRule p) => PenaltyProductionRule (FilterDiesRule p phi r t) where penalty _ FDDieRule = FDDieRule penalty _ (FDBaseRule _) = FDDieRule instance (LoopProductionRule p phi r) => LoopProductionRule (FilterDiesRule p phi r t) phi r where manyRef = FDBaseRule . manyRef many1Ref = FDBaseRule . many1Ref runFDRule :: (ProductionRule p) => FilterDiesRule p phi r t v -> p v runFDRule FDDieRule = die runFDRule (FDBaseRule r) = r -- | Filter dead branches from a given context-free grammar. filterDies :: forall phi t r rr. GContextFreeGrammar phi t r rr -> GContextFreeGrammar phi t r rr filterDies gram idx = runFDRule $ gram idx -- | Filter dead branches from a given context-free grammar. filterDiesP :: forall phi t r rr. GPenaltyContextFreeGrammar phi t r rr -> GPenaltyContextFreeGrammar phi t r rr filterDiesP gram idx = runFDRule $ gram idx -- | Filter dead branches from a given extended context-free grammar. filterDiesE :: forall phi t r rr. GExtendedContextFreeGrammar phi t r rr -> GExtendedContextFreeGrammar phi t r rr filterDiesE gram idx = runFDRule $ gram idx -- | Filter dead branches from a given context-free grammar. filterDiesPE :: forall phi t r rr. GPenaltyExtendedContextFreeGrammar phi t r rr -> GPenaltyExtendedContextFreeGrammar phi t r rr filterDiesPE gram idx = runFDRule $ gram idx -- | Filter dead branches from a given extended context-free grammar. filterDiesLE :: forall phi t r rr. GLExtendedContextFreeGrammar phi t r rr -> GLExtendedContextFreeGrammar phi t r rr filterDiesLE gram idx = runFDRule $ gram idx