module Data.Cfg.PredictSet (
Prediction,
Predictions,
predictSet,
ll1Info,
ll1InfoMap,
isLL1
) where
import Data.Cfg.Augment
import Data.Cfg.Cfg(Cfg(..))
import Data.Cfg.Collect
import Data.Cfg.FirstSet(firstsOfVs)
import Data.Cfg.LookaheadSet
import qualified Data.Map as M
import qualified Data.Set as S
predictSet :: (Ord t)
=> (AugNT nt -> LookaheadSet t)
-> (AugNT nt -> LookaheadSet t)
-> AugProduction t nt
-> LookaheadSet t
predictSet firstSet' followSet' (hd, vs)
= firstsOfVs firstSet' vs <> followSet' hd
type Prediction t nt = (LookaheadSet t, S.Set (AugProduction t nt))
type Predictions t nt = S.Set (Prediction t nt)
ll1Info :: (Cfg cfg (AugT t) (AugNT nt), Ord nt, Ord t)
=> cfg (AugT t) (AugNT nt)
-> (AugProduction t nt -> LookaheadSet t)
-> AugNT nt
-> Predictions t nt
ll1Info cfg predictSet' nt = ll1InfoMap cfg predictSet' M.! nt
ll1InfoMap :: forall cfg t nt
. (Cfg cfg (AugT t) (AugNT nt), Ord nt, Ord t)
=> cfg (AugT t) (AugNT nt)
-> (AugProduction t nt -> LookaheadSet t)
-> M.Map (AugNT nt) (Predictions t nt)
ll1InfoMap cfg predictSet' = mkMap mkPredictions $ S.toList $ nonterminals cfg
where
mkPredictions :: AugNT nt -> Predictions t nt
mkPredictions nt
= S.fromList $ f $ collectOnSecond $ collectOnFirst' lookaheadProds
where
lookaheadProds :: [(AugT t, AugProduction t nt)]
lookaheadProds = do
rhs <- S.toList $ productionRules cfg nt
let prod = (nt, rhs)
t <- S.toList $ toSet $ predictSet' prod
return (t, prod)
f :: [([AugT t], S.Set (AugProduction t nt))]
-> [(LookaheadSet t, S.Set (AugProduction t nt))]
f pairs = [(fromList la, ps) | (la, ps) <- pairs]
mkMap :: Ord k => (k -> v) -> [k] -> M.Map k v
mkMap f ks = M.fromList [(k, f k) | k <- ks]
isLL1 :: M.Map (AugNT nt) (Predictions t nt) -> Bool
isLL1 m = all (\ ps -> S.size ps == 1) $ M.elems m