module Data.Cfg.Cfg(
Cfg(..),
V(..),
Vs,
isNT,
isT,
bimapV,
bimapVs,
vocabulary,
usedVocabulary,
undeclaredVocabulary,
isFullyDeclared,
Production,
productions,
eqCfg ) where
import Control.Monad(liftM4)
import Control.Monad.Reader(ask)
import Data.Cfg.CPretty
import Data.Data(Data, Typeable)
import qualified Data.Set as S
import Text.PrettyPrint
class Cfg cfg t nt where
nonterminals :: cfg t nt -> S.Set nt
terminals :: cfg t nt -> S.Set t
productionRules :: cfg t nt -> nt -> S.Set (Vs t nt)
startSymbol :: cfg t nt -> nt
instance (Cfg cfg t nt) => CPretty (cfg t nt) (V t nt -> Doc) where
cpretty cfg = liftM4 vcat' ss ts nts prods
where
vcat' a b c d = vcat [a, b, c, d]
ss = do
prettyV <- ask
return (text "Start symbol:" <+> prettyV (NT $ startSymbol cfg))
ts = do
prettyV <- ask
return (text "Terminals:"
<+> fsep (punctuate comma
$ map (prettyV . T)
(S.toList $ terminals cfg)))
nts = do
prettyV <- ask
return (text "Nonterminals:"
<+> fsep (punctuate comma
$ map (prettyV . NT)
(S.toList $ nonterminals cfg)))
prods = do
prettyV <- ask
return (text "Productions:"
$$ nest 4
(vcat (map (prettyProd prettyV)
(zip [1..] $ productions cfg))))
where
prettyProd pv (n, (hd, rhs))
= hsep [parens (int n),
pv (NT hd), text "::=", rhs' <> text "."]
where
rhs' = hsep $ map pv rhs
data V t nt = T t
| NT nt
deriving (Eq, Ord, Show, Data, Typeable)
isT :: V t nt -> Bool
isT (T _) = True
isT _ = False
isNT :: V t nt -> Bool
isNT (NT _) = True
isNT _ = False
instance Functor (V t) where
fmap _f (T t) = T t
fmap f (NT nt) = NT $ f nt
bimapV :: (t -> t') -> (nt -> nt') -> V t nt -> V t' nt'
bimapV f _g (T t) = T $ f t
bimapV _f g (NT nt) = NT $ g nt
vocabulary :: (Cfg cfg t nt, Ord nt, Ord t) => cfg t nt -> S.Set (V t nt)
vocabulary cfg = S.map T (terminals cfg)
`S.union` S.map NT (nonterminals cfg)
type Vs t nt = [V t nt]
bimapVs :: (t -> t') -> (nt -> nt') -> Vs t nt -> Vs t' nt'
bimapVs f g = map (bimapV f g)
type Production t nt = (nt, Vs t nt)
productions :: (Cfg cfg t nt) => cfg t nt -> [Production t nt]
productions cfg = do
nt <- S.toList $ nonterminals cfg
vs <- S.toList $ productionRules cfg nt
return (nt, vs)
eqCfg :: forall cfg cfg' t nt
. (Cfg cfg t nt, Cfg cfg' t nt, Eq nt, Eq t)
=> cfg t nt -> cfg' t nt -> Bool
eqCfg cfg cfg' = to4Tuple cfg == to4Tuple cfg'
to4Tuple :: forall cfg t nt . (Cfg cfg t nt)
=> cfg t nt -> (nt, S.Set nt, S.Set t, [Production t nt])
to4Tuple cfg = (
startSymbol cfg,
nonterminals cfg,
terminals cfg,
productions cfg)
usedVocabulary :: (Cfg cfg t nt, Ord nt, Ord t)
=> cfg t nt -> S.Set (V t nt)
usedVocabulary cfg
= S.fromList
$ NT (startSymbol cfg) :
concat [ NT nt : vs | (nt, vs) <- productions cfg]
undeclaredVocabulary :: (Cfg cfg t nt, Ord nt, Ord t)
=> cfg t nt -> S.Set (V t nt)
undeclaredVocabulary cfg = usedVocabulary cfg S.\\ vocabulary cfg
isFullyDeclared :: (Cfg cfg t nt, Ord nt, Ord t) => cfg t nt -> Bool
isFullyDeclared = S.null . undeclaredVocabulary