{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# LANGUAGE PatternGuards #-}
module DFAMin (minimizeDFA) where
import AbsSyn
import Data.Map (Map)
import qualified Data.Map as Map
import Data.IntSet (IntSet)
import qualified Data.IntSet as IS
import Data.IntMap (IntMap)
import qualified Data.IntMap as IM
import Data.List as List
minimizeDFA :: Ord a => DFA Int a -> DFA Int a
minimizeDFA dfa@ DFA { dfa_start_states = starts,
dfa_states = statemap
}
= DFA { dfa_start_states = starts,
dfa_states = Map.fromList states }
where
equiv_classes = groupEquivStates dfa
numbered_states = number (length starts) equiv_classes
number _ [] = []
number n (ss:sss) =
case filter (`IS.member` ss) starts of
[] -> (n,ss) : number (n+1) sss
starts' -> zip starts' (repeat ss) ++ number n sss
states = [
let old_states = map (lookup statemap) (IS.toList equiv)
accs = map fix_acc (state_acc (head old_states))
out = IM.fromList [ (b, get_new old)
| State _ out <- old_states,
(b,old) <- IM.toList out ]
in (n, State accs out)
| (n, equiv) <- numbered_states
]
fix_acc acc = acc { accRightCtx = fix_rctxt (accRightCtx acc) }
fix_rctxt (RightContextRExp s) = RightContextRExp (get_new s)
fix_rctxt other = other
lookup m k = Map.findWithDefault (error "minimizeDFA") k m
get_new = lookup old_to_new
old_to_new :: Map Int Int
old_to_new = Map.fromList [ (s,n) | (n,ss) <- numbered_states,
s <- IS.toList ss ]
groupEquivStates :: (Ord a) => DFA Int a -> [IntSet]
groupEquivStates DFA { dfa_states = statemap }
= go init_p init_q
where
(accepting, nonaccepting) = Map.partition acc statemap
where acc (State as _) = not (List.null as)
nonaccepting_states = IS.fromList (Map.keys nonaccepting)
accept_map = {-# SCC "accept_map" #-}
foldl' (\m (n,s) -> Map.insertWith (++) (state_acc s) [n] m)
Map.empty
(Map.toList accepting)
accept_groups = map IS.fromList (Map.elems accept_map)
init_p = nonaccepting_states : accept_groups
init_q = accept_groups
bigmap :: IntMap (IntMap [SNum])
bigmap = IM.fromListWith (IM.unionWith (++))
[ (i, IM.singleton to [from])
| (from, state) <- Map.toList statemap,
(i,to) <- IM.toList (state_out state) ]
incoming :: Int -> IntSet -> IntSet
incoming i a = IS.fromList (concat ss)
where
map1 = IM.findWithDefault IM.empty i bigmap
ss = [ IM.findWithDefault [] s map1
| s <- IS.toList a ]
go p [] = p
go p (a:q) = go1 0 p q
where
go1 256 p q = go p q
go1 i p q = go1 (i+1) p' q'
where
(p',q') = go2 p [] q
x = incoming i a
go2 [] p' q = (p',q)
go2 (y:p) p' q
| IS.null i || IS.null d = go2 p (y:p') q
| otherwise = go2 p (i:d:p') q1
where
i = IS.intersection x y
d = IS.difference y x
q1 = replaceyin q
where
replaceyin [] =
if IS.size i < IS.size d then [i] else [d]
replaceyin (z:zs)
| z == y = i : d : zs
| otherwise = z : replaceyin zs