module FormalLanguage.CFG.Grammar.Util where
import Control.Lens hiding (Index,index)
import Data.Tuple (swap)
import Data.List (sort,nub,genericReplicate)
import FormalLanguage.CFG.Grammar.Types
isTerminal :: Symbol -> Bool
isTerminal = allOf folded (\case SynVar{} -> False; (SynTerm _ _) -> False; _ -> True) . _getSymbolList
isBindableTerminal :: Symbol -> Bool
isBindableTerminal = allOf folded (\case (Term _ _) -> True; _ -> False) . _getSymbolList
isSyntactic :: Symbol -> Bool
isSyntactic = allOf folded (\case SynVar{} -> True; _ -> False) . _getSymbolList
isSynStacked :: Symbol -> Bool
isSynStacked = allOf folded (\case SynVar{} -> True; Deletion -> True; _ -> False) . _getSymbolList
isAllSplit :: Symbol -> Bool
isAllSplit = allOf folded (\case (SynVar _ _ n _) -> n>1 ; _ -> False) . _getSymbolList
splitK0 :: Symbol -> Symbol
splitK0 = set (getSymbolList . traverse . splitK) 0
splitToFull :: Symbol -> Symbol
splitToFull (Symbol [SynVar s i n k]) = Symbol . genericReplicate n $ SynVar s i n 0
isSynTerm :: Symbol -> Bool
isSynTerm = allOf folded (\case (SynTerm _ _) -> True; _ -> False) . _getSymbolList
isEpsilon :: Symbol -> Bool
isEpsilon = allOf folded (\case Epsilon -> True; _ -> False) . _getSymbolList
dim :: Grammar -> Int
dim g
| null ls = error "no terminal symbol in grammar"
| all (l==) ls = l
| otherwise = error "inconsistent dimensionality"
where ls@(l:_) = map (length . _getSymbolList) $ g^.rules.folded.rhs
uniqueTermsWithTape :: Grammar -> [(SynTermEps , Tape)]
uniqueTermsWithTape = uniqueSynTermEpsWithTape . uniqueTerminalSymbols
uniqueBindableTermsWithTape :: Grammar -> [(SynTermEps , Tape)]
uniqueBindableTermsWithTape = uniqueSynTermEpsWithTape . uniqueBindableTerminalSymbols
uniqueSynVarsWithTape :: Grammar -> [(SynTermEps, Tape)]
uniqueSynVarsWithTape = uniqueSynTermEpsWithTape . uniqueSyntacticSymbols
uniqueSynTermsWithTape :: Grammar -> [(SynTermEps, Tape)]
uniqueSynTermsWithTape = uniqueSynTermEpsWithTape . uniqueSynTermSymbols
uniqueSynTermEpsWithTape :: [Symbol] -> [(SynTermEps, Tape)]
uniqueSynTermEpsWithTape = nub . sort
. map swap
. concatMap (zip [0..] . _getSymbolList)
uniqueTerminalSymbols :: Grammar -> [Symbol]
uniqueTerminalSymbols = nub . sort . filter isTerminal . toListOf (rules.folded.rhs.folded)
uniqueBindableTerminalSymbols :: Grammar -> [Symbol]
uniqueBindableTerminalSymbols = nub . sort . filter isBindableTerminal . toListOf (rules.folded.rhs.folded)
uniqueSyntacticSymbols :: Grammar -> [Symbol]
uniqueSyntacticSymbols g = nub . sort . filter isSyntactic $ g^..rules.folded.lhs
uniqueSynTermSymbols :: Grammar -> [Symbol]
uniqueSynTermSymbols = nub . sort . filter isSynTerm . toListOf (rules.folded.rhs.folded)
normalizeStartEpsilon :: Grammar -> Grammar
normalizeStartEpsilon = error "normalizeStartEpsilon: (re-)write me"
isLeftLinear :: Grammar -> Bool
isLeftLinear g = allOf folded isll $ g^.rules where
isll :: Rule -> Bool
isll (Rule l _ []) = isSyntactic l
isll (Rule l _ rs) = isSyntactic l && (allOf folded (not . isSyntactic) $ tail rs)
isRightLinear :: Grammar -> Bool
isRightLinear g = allOf folded isrl $ g^.rules where
isrl :: Rule -> Bool
isrl (Rule l _ []) = isSyntactic l
isrl (Rule l _ rs) = isSyntactic l && (allOf folded (not . isSyntactic) $ init rs)
isLinear :: Grammar -> Bool
isLinear g = allOf folded isl $ g^.rules where
isl :: Rule -> Bool
isl (Rule l _ []) = isSyntactic l
isl (Rule l _ rs) = isSyntactic l && (1 >= (length . filter isSyntactic $ rs))