diff options
Diffstat (limited to 'edit-lens/src/Control/FST.lhs')
-rw-r--r-- | edit-lens/src/Control/FST.lhs | 270 |
1 files changed, 203 insertions, 67 deletions
diff --git a/edit-lens/src/Control/FST.lhs b/edit-lens/src/Control/FST.lhs index 9298e11..9aa5341 100644 --- a/edit-lens/src/Control/FST.lhs +++ b/edit-lens/src/Control/FST.lhs | |||
@@ -1,3 +1,4 @@ | |||
1 | \begin{comment} | ||
1 | \begin{code} | 2 | \begin{code} |
2 | {-# LANGUAGE ScopedTypeVariables | 3 | {-# LANGUAGE ScopedTypeVariables |
3 | #-} | 4 | #-} |
@@ -7,16 +8,18 @@ Description: Finite state transducers with epsilon-transitions | |||
7 | -} | 8 | -} |
8 | module Control.FST | 9 | module Control.FST |
9 | ( FST(..) | 10 | ( FST(..) |
11 | -- * Using FSTs | ||
12 | , runFST, runFST', step | ||
10 | -- * Constructing FSTs | 13 | -- * Constructing FSTs |
11 | , wordFST | 14 | , wordFST |
12 | -- * Operations on FSTs | 15 | -- * Operations on FSTs |
13 | , productFST, restrictFST | 16 | , productFST, restrictOutput, restrictFST |
14 | -- * Debugging Utilities | 17 | -- * Debugging Utilities |
15 | , liveFST | 18 | , liveFST |
16 | ) where | 19 | ) where |
17 | 20 | ||
18 | import Data.Map.Strict (Map, (!?)) | 21 | import Data.Map.Lazy (Map, (!?), (!)) |
19 | import qualified Data.Map.Strict as Map | 22 | import qualified Data.Map.Lazy as Map |
20 | 23 | ||
21 | import Data.Set (Set) | 24 | import Data.Set (Set) |
22 | import qualified Data.Set as Set | 25 | import qualified Data.Set as Set |
@@ -24,7 +27,7 @@ import qualified Data.Set as Set | |||
24 | import Data.Sequence (Seq) | 27 | import Data.Sequence (Seq) |
25 | import qualified Data.Sequence as Seq | 28 | import qualified Data.Sequence as Seq |
26 | 29 | ||
27 | import Data.Maybe (mapMaybe, fromMaybe, isJust, fromJust) | 30 | import Data.Maybe (mapMaybe, fromMaybe, isJust, fromJust, isNothing) |
28 | 31 | ||
29 | import Numeric.Natural | 32 | import Numeric.Natural |
30 | 33 | ||
@@ -35,12 +38,28 @@ import Control.Monad.State.Strict | |||
35 | import Text.PrettyPrint.Leijen (Pretty(..)) | 38 | import Text.PrettyPrint.Leijen (Pretty(..)) |
36 | import qualified Text.PrettyPrint.Leijen as PP | 39 | import qualified Text.PrettyPrint.Leijen as PP |
37 | 40 | ||
38 | data FST state input output = FST | 41 | \end{code} |
42 | \end{comment} | ||
43 | |||
44 | \begin{defn}[Finite state transducers] | ||
45 | Unter einem finite state transducer verstehen wir ein 6-Tupel $(\Sigma, \Delta, Q, I, F, E)$ mit $\Sigma$ dem endlichen Eingabe-Alphabet, $\Delta$ dem endlichen Ausgabe-Alphabet, $Q$ einer endlichen Menge an Zuständen, $I \subset Q$ der Menge von initialen Zuständen, $F \subset Q$ der Menge von akzeptierenden Endzuständen, und $E \subset Q \times (\Sigma \cup \{ \epsilon \}) \times (\Delta \cup \{ \epsilon \}) \times Q$ der Transitionsrelation. | ||
46 | |||
47 | Semantisch ist ein finite state transducer ein endlicher Automat erweitert um die Fähigkeit bei Zustandsübergängen ein Symbol aus seinem Ausgabe-Alphabet an ein Ausgabe-Wort anzuhängen. | ||
48 | |||
49 | In Haskell lockern wir die Anforderung, dass die Ein- und Ausgabe-Alphabete endlich sein müssen und annotieren sie nur im Typsystem. | ||
50 | Zudem speichern wir die Transitionsrelation als multimap um effiziente lookups von Zustand-Eingabe-Paaren zu ermöglichen. | ||
51 | |||
52 | \begin{code} | ||
53 | dFSeata FST state input output = FST | ||
39 | { stInitial :: Set state | 54 | { stInitial :: Set state |
40 | , stTransition :: Map (state, Maybe input) (Set (state, Maybe output)) | 55 | , stTransition :: Map (state, Maybe input) (Set (state, Maybe output)) |
41 | , stAccept :: Set state | 56 | , stAccept :: Set state |
42 | } deriving (Show, Read) | 57 | } deriving (Show, Read) |
58 | \end{code} | ||
59 | \end{defn} | ||
43 | 60 | ||
61 | \begin{comment} | ||
62 | \begin{code} | ||
44 | instance (Show state, Show input, Show output) => Pretty (FST state input output) where | 63 | instance (Show state, Show input, Show output) => Pretty (FST state input output) where |
45 | pretty FST{..} = PP.vsep | 64 | pretty FST{..} = PP.vsep |
46 | [ PP.text "Initial states:" PP.</> PP.hang 2 (list . map (PP.text . show) $ Set.toAscList stInitial) | 65 | [ PP.text "Initial states:" PP.</> PP.hang 2 (list . map (PP.text . show) $ Set.toAscList stInitial) |
@@ -55,62 +74,164 @@ instance (Show state, Show input, Show output) => Pretty (FST state input output | |||
55 | ] | 74 | ] |
56 | where | 75 | where |
57 | label :: Show a => Maybe a -> PP.Doc | 76 | label :: Show a => Maybe a -> PP.Doc |
58 | label = maybe (PP.text "ɛ") (PP.text . show) | 77 | label = PP.text . maybe "ɛ" show |
59 | list :: [PP.Doc] -> PP.Doc | 78 | list :: [PP.Doc] -> PP.Doc |
60 | list = PP.encloseSep (PP.lbracket PP.<> PP.space) (PP.space PP.<> PP.rbracket) (PP.comma PP.<> PP.space) | 79 | list = PP.encloseSep (PP.lbracket PP.<> PP.space) (PP.space PP.<> PP.rbracket) (PP.comma PP.<> PP.space) |
80 | \end{code} | ||
81 | \end{comment} | ||
61 | 82 | ||
62 | runFST :: forall input output state. (Ord input, Ord output, Ord state) => FST state input output -> Seq input -> [Seq output] | 83 | Wir definieren die Auswertung von finite state transducers induktiv indem wir zunächst angeben wie ein einzelner Auswertungs-Schritt erfolgt. |
63 | runFST = fmap (map $ catMaybes . fmap (view _2) . view _2) . runFST' | 84 | |
64 | where | 85 | Hierzu kommentieren wir die Haskell-Implementierung eines Auswertungs-Schritts. |
65 | catMaybes = fmap fromJust . Seq.filter isJust | 86 | Notwendigerweise ist die Auswertung eines FSTs nicht deterministisch, wir produzieren daher eine Liste von möglichen Resultaten in keiner besonderen Reihenfolge. |
87 | |||
88 | \begin{code} | ||
89 | step :: forall input output state. (Ord input, Ord output, Ord state) | ||
90 | => FST state input output | ||
91 | -> Maybe state -- ^ Current state | ||
92 | -> Maybe input -- ^ Head of remaining input | ||
93 | -> [(Maybe input, state, Maybe output)] -- ^ Tuples of unconsumed input, next state, and produced output | ||
94 | step FST{..} Nothing inS = (\s -> (inS, s, Nothing)) <$> Set.toList stInitial | ||
95 | \end{code} | ||
96 | Ist kein vorheriger Schritt erfolgt so wählen wir einen initialen Zustand, konsumieren keine Eingabe, und produzieren keine Ausgabe. | ||
97 | |||
98 | \begin{code} | ||
99 | step FST{..} (Just c) inS = let | ||
100 | consuming = fromMaybe Set.empty $ Map.lookup (c, inS) stTransition | ||
101 | unconsuming = fromMaybe Set.empty $ Map.lookup (c, Nothing) stTransition | ||
102 | in Set.toList $ Set.map (\(n, mOut) -> (Nothing, n, mOut)) consuming `Set.union` Set.map (\(n, mOut) -> (inS, n, mOut)) unconsuming | ||
103 | \end{code} | ||
104 | Ansonsten wählen wir einen Eintrag aus der Transitionstabelle für den aktuellen Zustand, der entweder keine oder die gegebene Eingabe konsumiert. | ||
105 | Im Ergebnis geben wir den nächsten Zustand, die Ausgabe aus der Transitionstabelle, und ob die Eingabe konsumiert wurde an. | ||
66 | 106 | ||
107 | \begin{code} | ||
67 | runFST' :: forall input output state. (Ord input, Ord output, Ord state) | 108 | runFST' :: forall input output state. (Ord input, Ord output, Ord state) |
68 | => FST state input output | 109 | => FST state input output |
69 | -> Seq input | 110 | -> Seq input |
70 | -> [(state, Seq (state, Maybe output))] -- ^ Tuples of initial state and chosen transitions; not neccessarily finite | 111 | -> [(state, Seq (state, Maybe output))] -- ^ Tuples of initial state and chosen transitions; not neccessarily finite |
71 | -- ^ Compute all possible runs on the given input | 112 | -- ^ Compute all possible runs on the given input |
72 | runFST' fst Seq.Empty = guardAccept $ (\(_, st, _) -> (st, Seq.Empty)) <$> step fst Nothing Nothing | 113 | runFST' fst@FST{..} cs = do |
73 | runFST' fst cs = guardAccept $ do | 114 | initial <- view _2 <$> step fst Nothing Nothing -- Nondeterministically choose an initial state |
74 | initial <- view _2 <$> step fst Nothing Nothing | 115 | go (initial, Seq.Empty) cs -- Recursively extend the run consisting of only the initial state |
75 | go (initial, Seq.Empty) cs | ||
76 | where | 116 | where |
77 | guardAccept res = do | ||
78 | (initial, path) <- res | ||
79 | let | ||
80 | finalState | ||
81 | | (_ :> (st, _)) <- path = st | ||
82 | | otherwise = initial | ||
83 | guard $ finalState `Set.member` stAccept | ||
84 | return res | ||
85 | |||
86 | go :: (state, Seq (state, Maybe output)) -> Seq input-> [(state, Seq (state, Maybe output))] | 117 | go :: (state, Seq (state, Maybe output)) -> Seq input-> [(state, Seq (state, Maybe output))] |
118 | -- ^ Uses `step` on last state of run and nondeterministically chooses between alternatives given | ||
119 | \end{code} | ||
120 | |||
121 | Um alle möglichen Läufe auf einer gegebenen Eingabe zu berechnen wenden wir | ||
122 | rekursiv \texttt{step} auf den letzten Zustand des Laufs (und der verbleibenden | ||
123 | Eingabe) an bis keine Eingabe verbleibt und der letzte Zustand in der Menge der | ||
124 | akzeptierenden Endzustände liegt. | ||
125 | |||
126 | \begin{comment} | ||
127 | \begin{code} | ||
87 | go (initial, path) cs = do | 128 | go (initial, path) cs = do |
88 | let | 129 | let |
130 | -- | Determine last state of the run | ||
89 | current | 131 | current |
90 | | (_ :> (st, _)) <- path = st | 132 | | (_ :> (st, _)) <- path = st |
91 | | otherwise = initial | 133 | | otherwise = initial |
92 | (head, next, out) <- step fst (Just current) (Seq.lookup 0 cs) | 134 | case step fst (Just current) (Seq.lookup 0 cs) of |
93 | let | 135 | [] -> do |
94 | nPath = path :> (next, out) | 136 | guard $ current `Set.member` stAccept && Seq.null cs |
95 | ncs = maybe id (:<) head cs | 137 | return (initial, path) |
96 | go (initial, nPath) ncs | 138 | xs -> do |
97 | 139 | (head, next, out) <- xs | |
140 | let | ||
141 | nPath = path :> (next, out) | ||
142 | ncs | ||
143 | | (_ :< cs') <- cs = maybe id (:<) head cs' | ||
144 | | otherwise = Seq.Empty | ||
145 | go (initial, nPath) ncs | ||
146 | \end{code} | ||
147 | \end{comment} | ||
148 | |||
149 | Es ist gelegentlich nützlich nur die möglichen Ausgaben eines FST auf gegebener | ||
150 | Eingabe zu bestimmen, wir führen eine Hilfsfunktion auf Basis von | ||
151 | {\ttfamily runFST'} ein: | ||
152 | |||
153 | \begin{code} | ||
154 | runFST :: forall input output state. (Ord input, Ord output, Ord state) => FST state input output -> Seq input -> [Seq output] | ||
155 | -- ^ Compute all possible runs on the given input and return only their output | ||
156 | \end{code} | ||
157 | \begin{comment} | ||
158 | \begin{code} | ||
159 | runFST = fmap (map $ catMaybes . fmap (view _2) . view _2) . runFST' | ||
160 | where | ||
161 | catMaybes = fmap fromJust . Seq.filter isJust | ||
162 | \end{code} | ||
163 | \end{comment} | ||
164 | |||
165 | Wir können das Produkt zweier FSTs definieren. | ||
166 | Intuitiv wollen wir beide FSTs gleichzeitig ausführen und dabei sicherstellen, dass Ein- und Ausgabe der FSTs übereinstimmen\footnote{Da wir $\epsilon$-Transitionen in FSTs erlauben müssen wir uns festlegen wann eine $\epsilon$-Transition übereinstimmt mit einer anderen Transition. Wir definieren, dass $\epsilon$ als Eingabe mit jeder anderen Eingabe (inkl. einem weiteren $\epsilon$) übereinstimmt.}. | ||
167 | |||
168 | Hierfür berechnen wir das Graphen-Produkt der FSTs: | ||
169 | |||
170 | \begin{defn}[FST-Produkt] | ||
171 | Gegeben zwei finite state transducer $T = (\Sigma, \Delta, Q, I, F, E)$ und $T^\prime = (\Sigma^\prime, \Delta^\prime, Q^\prime, I^\prime, F^\prime, E^\prime)$ nennen wir $T^\times = (\Sigma^\times, \Delta^\times, Q^\times, I^\times, F^\times, E^\times)$ das Produkt $T^\times = T \times T^\prime$ von $T$ und $T^\prime$. | ||
172 | |||
173 | $T^\times$ bestimmt sich als das Graphenprodukt der beiden, die FSTs unterliegenden Graphen, wobei wir die Zustandsübergänge als Kanten mit Gewichten aus dem Boolschen Semiring auffassen: | ||
174 | |||
175 | \begin{align*} | ||
176 | \Sigma^\times & = \Sigma \cap \Sigma^\prime \\ | ||
177 | \Delta^\times & = \Delta \cap \Delta^\prime \\ | ||
178 | Q^\times & = Q \times Q^\prime \\ | ||
179 | I^\times & = I \times I^\prime \\ | ||
180 | F^\times & = F \times F^\prime \\ | ||
181 | E^\times & \subset Q^\times \times (\Sigma^\times \cup \{ \epsilon \}) \times (\Delta^\times \cup \{ \epsilon \}) \times Q^\times \\ | ||
182 | & = \left \{ ((q, q^\prime), \sigma, \delta, (\bar{q}, \bar{q^\prime})) \colon (q, \sigma, \delta, \bar{q}) \in E, (q^\prime, \sigma^\prime, \delta^\prime, \bar{q^\prime}) \in E^\prime, \sigma = \sigma^\prime, \delta = \delta^\prime \right \} | ||
183 | \end{align*} | ||
184 | \end{defn} | ||
98 | 185 | ||
99 | step :: forall input output state. (Ord input, Ord output, Ord state) | ||
100 | => FST state input output | ||
101 | -> Maybe state -- ^ Current state | ||
102 | -> Maybe input -- ^ Head of remaining input | ||
103 | -> [(Maybe input, state, Maybe output)] -- ^ Tuples of unconsumed input, next state, and produced output | ||
104 | step FST{..} Nothing inS = (\s -> (inS, s, Nothing)) <$> Set.toList stInitial | ||
105 | step FST{..} (Just c) inS = let | ||
106 | consuming = fromMaybe Set.empty $ Map.lookup (c, inS) stTransition | ||
107 | unconsuming = fromMaybe Set.empty $ Map.lookup (c, Nothing) stTransition | ||
108 | in Set.toList $ Set.map (\(n, mOut) -> (Nothing, n, mOut)) consuming `Set.union` Set.map (\(n, mOut) -> (inS, n, mOut)) unconsuming | ||
109 | 186 | ||
187 | \begin{code} | ||
188 | productFST :: forall state1 state2 input output. (Ord state1, Ord state2, Ord input, Ord output) => FST state1 input output -> FST state2 input output -> FST (state1, state2) input output | ||
189 | -- ^ Cartesian product on states, logical conjunction on transitions and state-properties (initial and accept) | ||
190 | -- | ||
191 | -- This is the "natural" (that is component-wise) product when considering FSTs to be weighted in the boolean semiring. | ||
192 | -- | ||
193 | -- Intuitively this corresponds to running both FSTs at the same time requiring them to produce the same output and agree on their input. | ||
194 | \end{code} | ||
110 | 195 | ||
111 | wordFST :: forall input output. Seq output -> FST Natural input output | 196 | \begin{comment} |
112 | -- ^ @wordFST str@ is the linear FST generating @str@ as output when given no input | 197 | \begin{code} |
113 | wordFST outs = FST | 198 | productFST fst1 fst2 = FST |
199 | { stInitial = Set.fromDistinctAscList $ stInitial fst1 `setProductList` stInitial fst2 | ||
200 | , stAccept = Set.fromDistinctAscList $ stAccept fst1 `setProductList` stAccept fst2 | ||
201 | , stTransition = Map.fromSet transitions . Set.fromDistinctAscList . mapMaybe filterTransition $ Map.keysSet (stTransition fst1) `setProductList` Map.keysSet (stTransition fst2) | ||
202 | } | ||
203 | where | ||
204 | setProductList :: forall a b. Set a -> Set b -> [(a, b)] | ||
205 | setProductList as bs = (,) <$> Set.toAscList as <*> Set.toAscList bs | ||
206 | filterTransition :: forall label. Eq label => ((state1, Maybe label), (state2, Maybe label)) -> Maybe ((state1, state2), Maybe label) | ||
207 | filterTransition ((st1, l1), (st2, l2)) | ||
208 | | l1 == l2 = Just ((st1, st2), l1) | ||
209 | | otherwise = Nothing | ||
210 | transitions :: ((state1, state2), Maybe input) -> Set ((state1, state2), Maybe output) | ||
211 | transitions ((st1, st2), inS) = Set.fromDistinctAscList . mapMaybe filterTransition $ out1 `setProductList` out2 | ||
212 | where | ||
213 | out1 = fromMaybe Set.empty (stTransition fst1 !? (st1, inS)) `Set.union` fromMaybe Set.empty (stTransition fst1 !? (st1, Nothing)) | ||
214 | out2 = fromMaybe Set.empty (stTransition fst2 !? (st2, inS)) `Set.union` fromMaybe Set.empty (stTransition fst2 !? (st2, Nothing)) | ||
215 | \end{code} | ||
216 | \end{comment} | ||
217 | |||
218 | Es ist später erforderlich einen FST derart einzuschränken, dass er eine gegebene Ausgabe produziert. | ||
219 | |||
220 | Hierzu nehmen wir das FST-Produkt mit einem FST, der, ungeachtet der Eingabe, immer die gegebene Ausgabe produziert. | ||
221 | Da die Ausgaben der beiden FSTs übereinstimmen müssen produziert das Produkt mit einem derartigen FST (solange dessen Ausgabe in keinem Sinne von der Eingabe abhängt) die gewünschte Ausgabe. | ||
222 | |||
223 | Zur Konstruktion eines derartigen \emph{Wort-FST}s nehmen wir Indizes im Ausgabe-Wort (natürliche Zahlen) als Zustände. | ||
224 | Übergänge sind immer entweder der Form $n \rightarrow \text{succ}(n)$, konsumieren keine Eingabe ($\epsilon$) und produzieren als Ausgabe das Zeichen am Index $n$ im Ausgabe-Wort, oder der Form $n \overset{(i, \epsilon)}{\rightarrow} n$, für jedes Eingabesymbol $i$ (um die Unabhängigkeit von der Eingabe sicherzustellen). | ||
225 | Weiter ist $0$ initial und $\text{length}(\text{Ausgabe})$ der einzige akzeptierende Endzustand. | ||
226 | |||
227 | \begin{code} | ||
228 | wordFST :: forall input output. (Ord input, Ord output) => Set input -> Seq output -> FST Natural input output | ||
229 | -- ^ @wordFST inps str@ is the linear FST generating @str@ as output when given any input with symbols in @inps@ | ||
230 | \end{code} | ||
231 | |||
232 | \begin{comment} | ||
233 | \begin{code} | ||
234 | wordFST inps outs = FST | ||
114 | { stInitial = Set.singleton 0 | 235 | { stInitial = Set.singleton 0 |
115 | , stAccept = Set.singleton l | 236 | , stAccept = Set.singleton l |
116 | , stTransition = Map.fromSet next states | 237 | , stTransition = Map.fromSet next states |
@@ -119,36 +240,50 @@ wordFST outs = FST | |||
119 | l :: Natural | 240 | l :: Natural |
120 | l = fromIntegral $ Seq.length outs | 241 | l = fromIntegral $ Seq.length outs |
121 | states :: Set (Natural, Maybe input) | 242 | states :: Set (Natural, Maybe input) |
122 | states = Set.fromDistinctAscList [ (n, Nothing) | n <- [0..pred l] ] | 243 | states |
244 | | Seq.null outs = Set.empty | ||
245 | | otherwise = Set.fromDistinctAscList [ (n, inp) | n <- [0..pred l], inp <- Nothing : map Just (Set.toList inps) ] | ||
123 | next :: (Natural, Maybe input) -> Set (Natural, Maybe output) | 246 | next :: (Natural, Maybe input) -> Set (Natural, Maybe output) |
124 | next (i, _) = Set.singleton (succ i, Just . Seq.index outs $ fromIntegral i) | 247 | next (i, _) = Set.fromList |
248 | [ (succ i, Just . Seq.index outs $ fromIntegral i) | ||
249 | , (i, Nothing) | ||
250 | ] | ||
251 | \end{code} | ||
252 | \end{comment} | ||
125 | 253 | ||
126 | productFST :: forall state1 state2 input output. (Ord state1, Ord state2, Ord input, Ord output) => FST state1 input output -> FST state2 input output -> FST (state1, state2) input output | 254 | Da \texttt{wordFST} zur Konstruktion eine komprehensive Menge aller Eingabesymbole benötigt verwenden wir im folgenden eine optimierte Variante des Produkts mit einem Wort-FST. |
127 | -- ^ Cartesian product on states, logical conjunction on transitions and state-properties (initial and accept) | 255 | |
128 | -- | 256 | \begin{code} |
129 | -- This is the "natural" (that is component-wise) product when considering FSTs to be weighted in the boolean semiring. | 257 | restrictOutput :: forall state input output. (Ord state, Ord input, Ord output) => Seq output -> FST state input output -> FST (Natural, state) input output |
130 | -- | 258 | -- ^ @restrictOutput out@ is equivalent to @productFST (wordFST inps out)@ where @inps@ is a comprehensive set of all input symbols @inp :: input@ |
131 | -- Intuitively this corresponds to running both FSTs at the same time requiring them to produce the same output and "agree" (epsilon agreeing with every character) on their input. | 259 | \end{code} |
132 | productFST fst1 fst2 = FST | 260 | |
133 | { stInitial = stInitial fst1 `setProduct` stInitial fst2 | 261 | \begin{comment} |
134 | , stAccept = stAccept fst1 `setProduct` stAccept fst2 | 262 | \begin{code} |
135 | , stTransition = Map.fromSet transitions . Set.fromList . mapMaybe filterTransition . Set.toAscList $ Map.keysSet (stTransition fst1) `setProduct` Map.keysSet (stTransition fst2) | 263 | restrictOutput out FST{..} = FST |
264 | { stInitial = Set.mapMonotonic (0,) stInitial | ||
265 | , stAccept = Set.mapMonotonic (l,) stAccept | ||
266 | , stTransition = Map.filter (not . Set.null) $ Map.fromList (concatMap noProgress $ Map.toList stTransition) `Map.union` Map.fromSet transitions (Set.fromDistinctAscList [((wSt, inSt), inSym) | wSt <- Set.toAscList wordStates, (inSt, inSym) <- Set.toAscList $ Map.keysSet stTransition]) | ||
136 | } | 267 | } |
137 | where | 268 | where |
138 | setProduct :: forall a b. Set a -> Set b -> Set (a, b) | 269 | l :: Natural |
139 | setProduct as bs = Set.fromDistinctAscList $ (,) <$> Set.toAscList as <*> Set.toAscList bs | 270 | l = fromIntegral $ Seq.length out |
140 | filterTransition :: forall label. Eq label => ((state1, Maybe label), (state2, Maybe label)) -> Maybe ((state1, state2), Maybe label) | 271 | wordStates :: Set Natural |
141 | filterTransition ((st1, Nothing ), (st2, in2 )) = Just ((st1, st2), in2) | 272 | wordStates |
142 | filterTransition ((st1, in1 ), (st2, Nothing )) = Just ((st1, st2), in1) | 273 | | Seq.null out = Set.empty |
143 | filterTransition ((st1, Just in1), (st2, Just in2)) | 274 | | otherwise = Set.fromDistinctAscList [0..pred l] |
144 | | in1 == in2 = Just ((st1, st2), Just in1) | 275 | noProgress :: ((state, Maybe input), Set (state, Maybe output)) -> [(((Natural, state), Maybe input), Set ((Natural, state), Maybe output))] |
145 | | otherwise = Nothing | 276 | noProgress ((inSt, inSym), outs) |
146 | transitions :: ((state1, state2), Maybe input) -> Set ((state1, state2), Maybe output) | 277 | = [ (((wState, inSt), inSym), Set.mapMonotonic (\(outSt, Nothing) -> ((wState, outSt), Nothing)) noOutput) | wState <- Set.toList wordStates, not $ Set.null noOutput ] |
147 | transitions ((st1, st2), inS) = Set.fromList . mapMaybe filterTransition . Set.toAscList $ out1 `setProduct` out2 | ||
148 | where | 278 | where |
149 | out1 = (fromMaybe Set.empty $ stTransition fst1 !? (st1, inS)) `Set.union` (fromMaybe Set.empty $ stTransition fst1 !? (st1, Nothing)) | 279 | noOutput = Set.filter (\(_, outSym) -> isNothing outSym) outs |
150 | out2 = (fromMaybe Set.empty $ stTransition fst2 !? (st2, inS)) `Set.union` (fromMaybe Set.empty $ stTransition fst2 !? (st2, Nothing)) | 280 | transitions :: ((Natural, state), Maybe input) -> Set ((Natural, state), Maybe output) |
281 | transitions ((l, inSt), inSym) = Set.fromDistinctAscList [ ((succ l, outSt), outSym) | (outSt, outSym@(Just _)) <- Set.toAscList $ stTransition ! (inSt, inSym), outSym == Seq.lookup (fromIntegral l) out ] | ||
282 | \end{code} | ||
283 | \end{comment} | ||
151 | 284 | ||
285 | \begin{comment} | ||
286 | \begin{code} | ||
152 | restrictFST :: forall state input output. (Ord state, Ord input, Ord output) => Set state -> FST state input output -> FST state input output | 287 | restrictFST :: forall state input output. (Ord state, Ord input, Ord output) => Set state -> FST state input output -> FST state input output |
153 | -- ^ @restrictFST states fst@ removes from @fst@ all states not in @states@ including transitions leading to or originating from them | 288 | -- ^ @restrictFST states fst@ removes from @fst@ all states not in @states@ including transitions leading to or originating from them |
154 | restrictFST sts FST{..} = FST | 289 | restrictFST sts FST{..} = FST |
@@ -170,7 +305,7 @@ liveFST :: forall state input output. (Ord state, Ord input, Ord output, Show st | |||
170 | liveFST fst@FST{..} = flip execState Set.empty $ mapM_ (depthSearch Set.empty) stInitial | 305 | liveFST fst@FST{..} = flip execState Set.empty $ mapM_ (depthSearch Set.empty) stInitial |
171 | where | 306 | where |
172 | stTransition' :: Map state (Set state) | 307 | stTransition' :: Map state (Set state) |
173 | stTransition' = Map.map (Set.map $ \(st, _) -> st) $ Map.mapKeysWith Set.union (\(st, _) -> st) stTransition | 308 | stTransition' = Map.map (Set.map (\(st, _) -> st)) $ Map.mapKeysWith Set.union (\(st, _) -> st) stTransition |
174 | depthSearch :: Set state -> state -> State (Set state) () | 309 | depthSearch :: Set state -> state -> State (Set state) () |
175 | depthSearch acc curr = do | 310 | depthSearch acc curr = do |
176 | let acc' = Set.insert curr acc | 311 | let acc' = Set.insert curr acc |
@@ -181,3 +316,4 @@ liveFST fst@FST{..} = flip execState Set.empty $ mapM_ (depthSearch Set.empty) s | |||
181 | alreadyLive <- get | 316 | alreadyLive <- get |
182 | mapM_ (depthSearch acc') $ next `Set.difference` alreadyLive | 317 | mapM_ (depthSearch acc') $ next `Set.difference` alreadyLive |
183 | \end{code} | 318 | \end{code} |
319 | \end{comment} | ||