{- 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 FlexibleInstances #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} module Text.GrammarCombinators.Utils.AssessSize ( assessSize ) where import Text.GrammarCombinators.Base newtype AssessSizeProductionRule (phi :: * -> *) (r :: * -> *) t v = ASPR { assessSizeRule :: Int } instance ProductionRule (AssessSizeProductionRule phi r t) where endOfInput = ASPR 1 die = ASPR 1 a ||| b = ASPR $ assessSizeRule a + assessSizeRule b a >>> b = ASPR $ assessSizeRule a + assessSizeRule b instance EpsProductionRule (AssessSizeProductionRule phi r t) where epsilon _ = ASPR 1 instance LiftableProductionRule (AssessSizeProductionRule phi r t) where epsilonL _ _ = ASPR 1 instance (Token t) => TokenProductionRule (AssessSizeProductionRule phi r t) t where token _ = ASPR 1 anyToken = ASPR 1 instance RecProductionRule (AssessSizeProductionRule phi r t) phi r where ref _ = ASPR 1 instance LoopProductionRule (AssessSizeProductionRule phi r t) phi r where manyRef _ = ASPR 1 many1Ref _ = ASPR 1 -- | Assess the size of a given grammar. Primitive rules ('token', 'ref', 'manyRef', 'many1Ref', 'epsilon') -- are counted as 1 point, combinators like '|||' or '>>>' just add the points of their left and -- right hand sides. Proposals for better metrics are welcome. assessSize :: forall phi r t rr . (Token t, FoldFam phi) => GExtendedContextFreeGrammar phi t r rr -> Int assessSize gram = let f idx = assessSizeRule $ gram idx in foldFam ((+) . f) 0