summaryrefslogtreecommitdiff
path: root/edit-lens/src/Control/DFST.lhs
diff options
context:
space:
mode:
authorGregor Kleen <gkleen@yggdrasil.li>2018-12-18 13:51:16 +0100
committerGregor Kleen <gkleen@yggdrasil.li>2018-12-18 13:51:16 +0100
commit46ae60eaca841b554ba20c6a2b7a15b43c12b4df (patch)
tree0bb06127a0e08e75f8be755f5a5dfb1702b627b6 /edit-lens/src/Control/DFST.lhs
parentb0b18979d5ccd109d5a56937396acdeb85c857aa (diff)
downloadincremental-dfsts-46ae60eaca841b554ba20c6a2b7a15b43c12b4df.tar
incremental-dfsts-46ae60eaca841b554ba20c6a2b7a15b43c12b4df.tar.gz
incremental-dfsts-46ae60eaca841b554ba20c6a2b7a15b43c12b4df.tar.bz2
incremental-dfsts-46ae60eaca841b554ba20c6a2b7a15b43c12b4df.tar.xz
incremental-dfsts-46ae60eaca841b554ba20c6a2b7a15b43c12b4df.zip
Much ado about nothing
Diffstat (limited to 'edit-lens/src/Control/DFST.lhs')
-rw-r--r--edit-lens/src/Control/DFST.lhs57
1 files changed, 42 insertions, 15 deletions
diff --git a/edit-lens/src/Control/DFST.lhs b/edit-lens/src/Control/DFST.lhs
index eae2e66..6e16c74 100644
--- a/edit-lens/src/Control/DFST.lhs
+++ b/edit-lens/src/Control/DFST.lhs
@@ -1,6 +1,7 @@
1\begin{comment}
1\begin{code} 2\begin{code}
2{-# LANGUAGE ScopedTypeVariables 3{-# LANGUAGE ScopedTypeVariables
3#-} 4 #-}
4 5
5{-| 6{-|
6Description: Deterministic finite state transducers 7Description: Deterministic finite state transducers
@@ -11,8 +12,8 @@ module Control.DFST
11 , toFST 12 , toFST
12 ) where 13 ) where
13 14
14import Data.Map.Strict (Map, (!?)) 15import Data.Map.Lazy (Map, (!?))
15import qualified Data.Map.Strict as Map 16import qualified Data.Map.Lazy as Map
16 17
17import Data.Set (Set) 18import Data.Set (Set)
18import qualified Data.Set as Set 19import qualified Data.Set as Set
@@ -29,18 +30,34 @@ import Control.Monad.State
29 30
30import Control.FST (FST(FST)) 31import Control.FST (FST(FST))
31import qualified Control.FST as FST 32import qualified Control.FST as FST
33\end{code}
34\end{comment}
32 35
36\begin{defn}[deterministic finite state transducer]
37 Wir nennen einen FST \emph{deterministic}, wenn jedes Paar aus Ausgabezustand und Eingabesymbol maximal eine Transition zulässt, $\epsilon$-Transitionen keine Schleifen bilden und die Menge von initialen Zustände einelementig ist.
33 38
39 Zusätzlich ändern wir die Darstellung indem wir $\epsilon$-Transitionen kontrahieren.
40 Wir erweitern hierfür die Ausgabe pro Transition von einem einzelnen Zeichen zu einem Wort beliebiger Länge und fügen, bei jeder Kontraktion einer $\epsilon$-Transition $A \rightarrow B$, die Ausgabe der Transition vorne an die Ausgabe aller Transitionen $B \rightarrow \ast$ von $B$ an.
41\end{defn}
42
43\begin{code}
34data DFST state input output = DFST 44data DFST state input output = DFST
35 { stInitial :: state 45 { stInitial :: state
36 , stTransition :: Map (state, input) (state, Seq output) 46 , stTransition :: Map (state, input) (state, Seq output)
37 -- ^ All @(s, c)@-combinations not mapped are assumed to map to @(s, Nothing)@
38 , stAccept :: Set state 47 , stAccept :: Set state
39 } 48 }
49\end{code}
40 50
51Die in der Definition von DFSTs beschriebene Umwandlung lässt sich umkehren, sich also jeder DFST auch als FST auffassen.
41 52
53Hierfür trennen wir Transitionen $A \overset{(\sigma, \delta^\ast)}{\rightarrow} B$ mit Eingabe $\sigma$ und Ausgabe-Wort $\delta^\ast = \delta_1 \delta_2 \ldots \delta_n$ in eine Serie von Transitionen $A \overset{(\sigma, \delta_1)}{\rightarrow} A_1 \overset{(\epsilon, \delta_2)}{\rightarrow} \ldots \overset{(\epsilon, \delta_n)}{\rightarrow} B$ auf.
54
55\begin{code}
42toFST :: forall state input output. (Ord state, Ord input, Ord output) => DFST state input output -> FST (state, Maybe (input, Natural)) input output 56toFST :: forall state input output. (Ord state, Ord input, Ord output) => DFST state input output -> FST (state, Maybe (input, Natural)) input output
43-- ^ Split apart non-singleton outputs into a series of epsilon-transitions 57-- ^ View a DFST as a FST splitting apart non-singleton outputs into a series of epsilon-transitions
58\end{code}
59\begin{comment}
60\begin{code}
44toFST DFST{..} = flip execState initialFST $ forM_ (Map.toList stTransition) handleTransition 61toFST DFST{..} = flip execState initialFST $ forM_ (Map.toList stTransition) handleTransition
45 where 62 where
46 initialFST = FST 63 initialFST = FST
@@ -62,21 +79,31 @@ toFST DFST{..} = flip execState initialFST $ forM_ (Map.toList stTransition) han
62 -- Both calls to `handleTransition'` (one in `handleTransition`, the other below) satisfy one of the above cases 79 -- Both calls to `handleTransition'` (one in `handleTransition`, the other below) satisfy one of the above cases
63 addTransition (from, inS) (next, Just outS) 80 addTransition (from, inS) (next, Just outS)
64 handleTransition' next Nothing oo to 81 handleTransition' next Nothing oo to
65 82\end{code}
83\end{comment}
84
85Das Ausführen eines DFST auf eine gegebene Eingabe ist komplett analog zum Ausführen eines FST.
86Unsere Implementierung nutzt die restriktivere Struktur aus unserer Definition von DFSTs um den Determinismus bereits im Typsystem zu kodieren.
87
88\begin{code}
66runDFST :: forall state input output. (Ord state, Ord input) => DFST state input output -> Seq input -> Maybe (Seq output) 89runDFST :: forall state input output. (Ord state, Ord input) => DFST state input output -> Seq input -> Maybe (Seq output)
67runDFST dfst@DFST{..} str = let (finalState, str') = runDFST' dfst stInitial str Seq.empty 90\end{code}
68 in str' <$ guard (finalState `Set.member` stAccept) 91\begin{comment}
92\begin{code}
93runDFST dfst@DFST{..} str = do
94 let (str', finalState') = runDFST' dfst stInitial str Seq.empty
95 finalState <- finalState'
96 str' <$ guard (finalState `Set.member` stAccept)
69 97
70runDFST' :: forall state input output. (Ord state, Ord input) 98runDFST' :: forall state input output. (Ord state, Ord input)
71 => DFST state input output 99 => DFST state input output
72 -> state -- ^ Current state 100 -> state -- ^ Current state
73 -> Seq input -- ^ Remaining input 101 -> Seq input -- ^ Remaining input
74 -> Seq output -- ^ Accumulator containing previous output 102 -> Seq output -- ^ Accumulator containing previous output
75 -> (state, Seq output) -- ^ Next state, altered output 103 -> (Seq output, Maybe state) -- ^ Altered output, Next state
76runDFST' _ st Empty acc = (st, acc) 104runDFST' _ st Empty acc = (acc, Just st)
77runDFST' dfst@DFST{..} st (c :<| cs) acc 105runDFST' dfst@DFST{..} st (c :<| cs) acc = case stTransition !? (st, c) of
78 | Just (st', mc') <- stTransition !? (st, c) 106 Just (st', mc') -> runDFST' dfst st' cs $ acc <> mc'
79 = runDFST' dfst st' cs $ acc <> mc' 107 Nothing -> (acc, Nothing)
80 | otherwise
81 = runDFST' dfst st cs acc
82\end{code} 108\end{code}
109\end{comment}