{-# LANGUAGE ScopedTypeVariables, DeriveAnyClass, DeriveGeneric
, FlexibleContexts, UndecidableInstances, StandaloneDeriving
, OverloadedStrings #-}
module Text.ANTLR.Allstar.ATN where
import Text.ANTLR.Grammar
import Text.ANTLR.Allstar.Stacks
import Text.ANTLR.Set (Set(..), empty, fromList, toList, Hashable, Generic)
import Text.ANTLR.Pretty
type Gamma nt = Stacks (ATNState nt)
data ATN s nt t = ATN
{ _Δ :: Set (Transition s nt t)
} deriving (Eq, Ord, Show)
instance (Prettify s, Prettify nt, Prettify t, Hashable nt, Hashable t, Eq nt, Eq t) => Prettify (ATN s nt t) where
prettify atn = do
pLine "_Δ:"
incrIndent 4
prettify $ _Δ atn
incrIndent (-4)
type Transition s nt t = (ATNState nt, Edge s nt t, ATNState nt)
data ATNState nt = Start nt
| Middle nt Int Int
| Accept nt
deriving (Eq, Generic, Hashable, Ord, Show)
instance (Prettify nt) => Prettify (ATNState nt) where
prettify (Start nt) = pStr "p_" >> prettify nt
prettify (Accept nt) = pStr "p'_" >> prettify nt
prettify (Middle nt i j) = do
pStr "p_{"
prettify i
pStr ","
prettify j
pStr "}"
data Edge s nt t =
NTE nt
| TE t
| PE (Predicate ())
| ME (Mutator ())
| Epsilon
deriving (Eq, Generic, Hashable, Ord, Show)
instance (Prettify s, Prettify nt, Prettify t) => Prettify (Edge s nt t) where
prettify x = do
pStr "--"
case x of
NTE nt -> prettify nt
TE t -> prettify t
PE p -> prettify p
ME m -> prettify m
Epsilon -> pStr "ε"
pStr "-->"
atnOf
:: forall nt t s. (Eq nt, Eq t, Hashable nt, Hashable t)
=> Grammar s nt t -> ATN s nt t
atnOf g = let
_Δ :: Int -> Production s nt t -> [Transition s nt t]
_Δ i (Production lhs rhs) = let
st :: nt -> Int -> Int -> ATNState nt
st = Middle
_Δ' :: Int -> ProdElem nt t -> Transition s nt t
_Δ' k (NT nt) = (st lhs i (k - 1), NTE nt, st lhs i k)
_Δ' k (T t) = (st lhs i (k - 1), TE t, st lhs i k)
sϵ = (Start lhs, Epsilon, Middle lhs i 0)
fϵ _α = (Middle lhs i (length _α), Epsilon, Accept lhs)
sem_state _α = Middle lhs i (length _α + 1)
sϵ_sem _π _α = [(Start lhs, Epsilon, sem_state _α), (sem_state _α, PE _π, Middle lhs i 0)]
fϵ_sem = fϵ
sϵ_mut = sϵ
fϵ_mut _μ = (Middle lhs i 0, ME _μ, Accept lhs)
in (case rhs of
(Prod Pass _α) -> [sϵ, fϵ _α] ++ zipWith _Δ' [1..(length _α)] _α
(Prod (Sem _π) _α) -> sϵ_sem _π _α ++ [fϵ_sem _α] ++ zipWith _Δ' [1..(length _α)] _α
(Prod (Action _μ) _) -> [sϵ_mut, fϵ_mut _μ]
)
in ATN
{ _Δ = fromList $ concat $ zipWith _Δ [0..length (ps g)] $ ps g
}