summaryrefslogtreecommitdiff
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
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
-rw-r--r--.gitignore3
-rw-r--r--edit-lens/package.yaml69
-rw-r--r--edit-lens/src/Control/DFST.lhs57
-rw-r--r--edit-lens/src/Control/DFST/Lens.lhs412
-rw-r--r--edit-lens/src/Control/Edit.lhs6
-rw-r--r--edit-lens/src/Control/FST.lhs270
-rw-r--r--edit-lens/src/Control/Lens/Edit.lhs10
-rw-r--r--edit-lens/test/Control/DFST/LensTest.hs35
-rw-r--r--edit-lens/test/Control/DFSTTest.hs101
-rw-r--r--edit-lens/test/Control/FSTTest.hs187
-rw-r--r--edit-lens/test/Driver.hs1
-rw-r--r--interactive-edit-lens/ChangeLog.md5
-rw-r--r--interactive-edit-lens/LICENSE30
-rw-r--r--interactive-edit-lens/Setup.hs2
-rw-r--r--interactive-edit-lens/package.yaml53
-rw-r--r--interactive-edit-lens/src/Interact.hs271
-rw-r--r--interactive-edit-lens/src/Interact/Types.hs120
-rw-r--r--interactive-edit-lens/src/Main.hs94
-rw-r--r--literature.meta.yml5
-rw-r--r--stack.nix2
-rw-r--r--stack.yaml4
-rwxr-xr-xthesis.pdf.gup7
-rw-r--r--thesis.tex14
23 files changed, 1495 insertions, 263 deletions
diff --git a/.gitignore b/.gitignore
index dbb9822..8bf5f01 100644
--- a/.gitignore
+++ b/.gitignore
@@ -5,3 +5,6 @@ literature.pdf
5/thesis.meta.yml 5/thesis.meta.yml
6/thesis.pdf 6/thesis.pdf
7**/*.cabal 7**/*.cabal
8**.log
9**.prof
10**.prof.*
diff --git a/edit-lens/package.yaml b/edit-lens/package.yaml
index b506ec1..88a35ca 100644
--- a/edit-lens/package.yaml
+++ b/edit-lens/package.yaml
@@ -9,32 +9,38 @@ extra-source-files:
9 - ChangeLog.md 9 - ChangeLog.md
10git: https://git.yggdrasil.li/gkleen/pub/bachelor-thesis 10git: https://git.yggdrasil.li/gkleen/pub/bachelor-thesis
11 11
12default-extensions:
13 - TypeFamilies
14 - FlexibleContexts
15 - FlexibleInstances
16 - MultiParamTypeClasses
17 - FunctionalDependencies
18 - AllowAmbiguousTypes
19 - TypeApplications
20 - GADTs
21 - RecordWildCards
22 - NamedFieldPuns
23 - PatternGuards
24 - TupleSections
25 - RankNTypes
26 - ViewPatterns
27 - DerivingStrategies
28
29dependencies:
30 - base
31 - lens
32 - containers
33 - composition-tree
34 - monad-memo
35 - Diff
36 - mtl
37 - wl-pprint
38 - intervals
39
40# ghc-options: [ -O2 ]
41
12library: 42library:
13 default-extensions:
14 - TypeFamilies
15 - FlexibleContexts
16 - FlexibleInstances
17 - MultiParamTypeClasses
18 - FunctionalDependencies
19 - AllowAmbiguousTypes
20 - TypeApplications
21 - GADTs
22 - RecordWildCards
23 - NamedFieldPuns
24 - PatternGuards
25 - TupleSections
26 - RankNTypes
27 - ViewPatterns
28 source-dirs: src 43 source-dirs: src
29 dependencies:
30 - base
31 - lens
32 - containers
33 - composition-tree
34 - Diff
35 - mtl
36 - wl-pprint
37 - intervals
38 exposed-modules: 44 exposed-modules:
39 - Control.Edit 45 - Control.Edit
40 - Control.Lens.Edit 46 - Control.Lens.Edit
@@ -42,4 +48,17 @@ library:
42 - Control.FST 48 - Control.FST
43 - Control.DFST.Lens 49 - Control.DFST.Lens
44 50
45 51tests:
52 test:
53 source-dirs:
54 - test
55 - src
56 main: Driver.hs
57 dependencies:
58 - tasty
59 - tasty-discover
60 - tasty-hedgehog
61 - tasty-hunit
62 - HUnit
63 - hedgehog
64 - deepseq
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}
diff --git a/edit-lens/src/Control/DFST/Lens.lhs b/edit-lens/src/Control/DFST/Lens.lhs
index 95be34e..fe33bd6 100644
--- a/edit-lens/src/Control/DFST/Lens.lhs
+++ b/edit-lens/src/Control/DFST/Lens.lhs
@@ -1,12 +1,14 @@
1\begin{comment}
1\begin{code} 2\begin{code}
2{-# LANGUAGE ScopedTypeVariables 3{-# LANGUAGE ScopedTypeVariables
3 , TemplateHaskell 4 , TemplateHaskell
4 , ConstraintKinds 5 , ConstraintKinds
6 , GeneralizedNewtypeDeriving
5#-} 7#-}
6 8
7module Control.DFST.Lens 9module Control.DFST.Lens
8 ( StringEdit(..) 10 ( StringEdit(..), sePos, seInsertion
9 , StringEdits(..) 11 , StringEdits(..), _StringEdits, _SEFail, stringEdits
10 , insert, delete, replace 12 , insert, delete, replace
11 , DFSTAction(..), DFSTComplement 13 , DFSTAction(..), DFSTComplement
12 , dfstLens 14 , dfstLens
@@ -16,7 +18,7 @@ module Control.DFST.Lens
16 18
17import Control.DFST 19import Control.DFST
18import Control.FST hiding (stInitial, stTransition, stAccept) 20import Control.FST hiding (stInitial, stTransition, stAccept)
19import qualified Control.FST as FST (stInitial, stTransition, stAccept) 21import qualified Control.FST as FST (stInitial, stTransition, stAccept, step)
20import Control.Lens.Edit 22import Control.Lens.Edit
21import Control.Lens 23import Control.Lens
22import Control.Lens.TH 24import Control.Lens.TH
@@ -32,11 +34,11 @@ import Data.Sequence (Seq((:<|), (:|>)))
32import qualified Data.Sequence as Seq 34import qualified Data.Sequence as Seq
33import Data.Set (Set) 35import Data.Set (Set)
34import qualified Data.Set as Set 36import qualified Data.Set as Set
35import Data.Map.Strict (Map) 37import Data.Map.Lazy (Map)
36import qualified Data.Map.Strict as Map 38import qualified Data.Map.Lazy as Map
37 39
38import Data.Compositions.Snoc (Compositions) 40import Data.Compositions (Compositions)
39import qualified Data.Compositions.Snoc as Comp 41import qualified Data.Compositions as Comp
40 42
41import Data.Algorithm.Diff (Diff, getDiff) 43import Data.Algorithm.Diff (Diff, getDiff)
42import qualified Data.Algorithm.Diff as Diff 44import qualified Data.Algorithm.Diff as Diff
@@ -48,69 +50,72 @@ import Data.Function (on)
48import Data.Foldable (toList) 50import Data.Foldable (toList)
49import Data.List (partition) 51import Data.List (partition)
50 52
51import Debug.Trace 53import Control.Exception (assert)
52 54
55import System.IO.Unsafe
56import Text.PrettyPrint.Leijen (Pretty(..))
53 57
54data StringEdit char = Insert { _sePos :: Natural, _seInsertion :: char } 58\end{code}
55 | Delete { _sePos :: Natural } 59\end{comment}
60
61
62Wir betrachten, zur Einfachheit, ein minimiales Set von Edits auf Strings\footnote{Wie in der Konstruktion zum Longest Common Subsequence Problem}:
63
64\begin{defn}[Atomare edits of strings]
65\begin{code}
66data StringEdit pos char = Insert { _sePos :: pos, _seInsertion :: char }
67 | Delete { _sePos :: pos }
56 deriving (Eq, Ord, Show, Read) 68 deriving (Eq, Ord, Show, Read)
57 69
70-- Automatically derive van-leerhoven-lenses:
71--
72-- @sePos :: Lens' (StringEdits pos char) pos@
73-- @seInsertion :: Traversal' (StringEdits pos char) char@
58makeLenses ''StringEdit 74makeLenses ''StringEdit
75\end{code}
76\end{defn}
59 77
60data StringEdits char = StringEdits (Seq (StringEdit char)) 78Atomare edits werden, als Liste, zu edits komponiert.
61 | SEFail 79Wir führen einen speziellen edit ein, der nicht-Anwendbarkeit der edits repräsentiert:
80\begin{code}
81data StringEdits pos char = StringEdits (Seq (StringEdit pos char))
82 | SEFail
62 deriving (Eq, Ord, Show, Read) 83 deriving (Eq, Ord, Show, Read)
63 84
64makePrisms ''StringEdits 85makePrisms ''StringEdits
65 86
66stringEdits :: Traversal' (StringEdits char) (StringEdit char) 87stringEdits :: Traversal (StringEdits pos char) (StringEdits pos' char') (StringEdit pos char) (StringEdit pos' char')
88\end{code}
89\begin{comment}
90\begin{code}
67stringEdits = _StringEdits . traverse 91stringEdits = _StringEdits . traverse
68 92\end{code}
69affected :: forall char. StringEdits char -> Maybe (Interval Natural) 93\end{comment}
70-- ^ For a given set of edits @es@ return the interval @i = a ... b@ such that for any given string @str@ of sufficient length the following holds: 94\begin{code}
71-- 95insert :: pos -> char -> StringEdits pos char
72-- - For all @n :: Natural@: @n < a ==> str ! n == (str `apply` es) ! n@ 96\end{code}
73-- - There exists a @k :: Integer@ such that for all @n :: Integer@: @n > b ==> str ! (n + k) == (str `apply` es) ! n@ 97\begin{comment}
74-- 98\begin{code}
75-- Intuitively: for any character @c@ of the new string @str `apply` es@ there exists a corresponding character in @str@ (offset by either 0 or a constant shift @k@) if the index of @c@ is /not/ contained in @affected es@.
76affected SEFail = Nothing
77affected (StringEdits es) = Just . toInterval $ go es Map.empty
78 where
79 toInterval :: Map Natural Integer -> Interval Natural
80 toInterval map
81 | Just (((minK, _), _), ((maxK, _), _)) <- (,) <$> Map.minViewWithKey map <*> Map.maxViewWithKey map
82 = let
83 maxV' = maximum . (0 :) $ do
84 offset <- [0..maxK]
85 v <- maybeToList $ Map.lookup (maxK - offset) map
86 v' <- maybeToList . fmap fromInteger $ negate v <$ guard (v <= 0)
87 guard $ v' >= succ offset
88 return $ v' - offset
89 in (minK Int.... maxK + maxV')
90 | otherwise
91 = Int.empty
92 go :: Seq (StringEdit char) -> Map Natural Integer -> Map Natural Integer
93 go Seq.Empty offsets = offsets
94 go (es :> e) offsets = go es offsets'
95 where
96 p = e ^. sePos
97 p' = fromIntegral $ Map.foldrWithKey (\k o p -> bool (fromIntegral p) (o + p) $ k < fromIntegral p) (fromIntegral p) offsets
98 offsets' = Map.alter (Just . myOffset . fromMaybe 0) p offsets
99 myOffset :: Integer -> Integer
100 myOffset
101 | Insert _ _ <- e = pred
102 | Delete _ <- e = succ
103
104insert :: Natural -> char -> StringEdits char
105insert n c = StringEdits . Seq.singleton $ Insert n c 99insert n c = StringEdits . Seq.singleton $ Insert n c
106 100\end{code}
107delete :: Natural -> StringEdits char 101\end{comment}
102\begin{code}
103delete :: pos -> StringEdits pos char
104\end{code}
105\begin{comment}
106\begin{code}
108delete n = StringEdits . Seq.singleton $ Delete n 107delete n = StringEdits . Seq.singleton $ Delete n
109 108\end{code}
110replace :: Natural -> char -> StringEdits char 109\end{comment}
110\begin{code}
111replace :: Eq pos => pos -> char -> StringEdits pos char
112\end{code}
113\begin{comment}
114\begin{code}
111replace n c = insert n c <> delete n 115replace n c = insert n c <> delete n
112 116
113instance Monoid (StringEdits char) where 117-- | Rudimentarily optimize edit composition
118instance Eq pos => Monoid (StringEdits pos char) where
114 mempty = StringEdits Seq.empty 119 mempty = StringEdits Seq.empty
115 SEFail `mappend` _ = SEFail 120 SEFail `mappend` _ = SEFail
116 _ `mappend` SEFail = SEFail 121 _ `mappend` SEFail = SEFail
@@ -122,12 +127,16 @@ instance Monoid (StringEdits char) where
122 , n == n' 127 , n == n'
123 = StringEdits bs `mappend` StringEdits as 128 = StringEdits bs `mappend` StringEdits as
124 | otherwise = StringEdits $ x `mappend` y 129 | otherwise = StringEdits $ x `mappend` y
130\end{code}
131\end{comment}
125 132
126instance Module (StringEdits char) where 133Da wir ein minimales set an atomaren edits gewählt haben, ist die Definiton der Modulnstruktur über Strings des passenden Alphabets recht einfach:
127 type Domain (StringEdits char) = Seq char 134\begin{code}
135instance Module (StringEdits Natural char) where
136 type Domain (StringEdits Natural char) = Seq char
128 apply str SEFail = Nothing 137 apply str SEFail = Nothing
129 apply str (StringEdits Seq.Empty) = Just str 138 apply str (StringEdits Seq.Empty) = Just str
130 apply str (StringEdits (es :|> Insert n c)) = (flip apply) (StringEdits es) =<< go str n c 139 apply str (StringEdits (es :|> Insert n c)) = flip apply (StringEdits es) =<< go str n c
131 where 140 where
132 go Seq.Empty n c 141 go Seq.Empty n c
133 | n == 0 = Just $ Seq.singleton c 142 | n == 0 = Just $ Seq.singleton c
@@ -135,7 +144,7 @@ instance Module (StringEdits char) where
135 go str@(x :<| xs) n c 144 go str@(x :<| xs) n c
136 | n == 0 = Just $ c <| str 145 | n == 0 = Just $ c <| str
137 | otherwise = (x <|) <$> go xs (pred n) c 146 | otherwise = (x <|) <$> go xs (pred n) c
138 apply str (StringEdits (es :|> Delete n)) = (flip apply) (StringEdits es) =<< go str n 147 apply str (StringEdits (es :|> Delete n)) = flip apply (StringEdits es) =<< go str n
139 where 148 where
140 go Seq.Empty _ = Nothing 149 go Seq.Empty _ = Nothing
141 go (x :<| xs) n 150 go (x :<| xs) n
@@ -146,99 +155,128 @@ instance Module (StringEdits char) where
146 divInit = StringEdits . Seq.unfoldl go . (0,) 155 divInit = StringEdits . Seq.unfoldl go . (0,)
147 where 156 where
148 go (_, Seq.Empty) = Nothing 157 go (_, Seq.Empty) = Nothing
149 go (n, (c :<| cs)) = Just ((succ n, cs), Insert n c) 158 go (n, c :<| cs ) = Just ((succ n, cs), Insert n c)
150 159
151\end{code} 160\end{code}
152 161
153% TODO Make notation mathy 162% TODO Make notation mathy
154 163
155Um zunächst eine asymmetrische edit-lens `StringEdits -> StringEdits` mit akzeptabler Komplexität für einen bestimmten `DFST s` (entlang der \emph{Richtung} des DFSTs) zu konstruieren möchten wir folgendes Verfahren anwenden: 164Um zunächst eine asymmetrische edit-lens \texttt{StringEdits -> StringEdits} mit akzeptabler Komplexität für einen bestimmten DFST (entlang der \emph{Richtung} des DFSTs) zu konstruieren möchten wir folgendes Verfahren anwenden:
156 165
157Gegeben eine Sequenz (`StringEdits`) von zu übersetzenden Änderungen genügt es die Übersetzung eines einzelnen `StringEdit`s in eine womöglich längere Sequenz von `StringEdits` anzugeben, alle `StringEdits` aus der Sequenz zu übersetzen (hierbei muss auf die korrekte Handhabung des Komplements geachtet werden) und jene Übersetzungen dann zu concatenieren. 166Gegeben eine Sequenz von zu übersetzenden Änderungen genügt es die Übersetzung eines einzelnen \texttt{StringEdit}s in eine womöglich längere Sequenz von \texttt{StringEdits} anzugeben, alle \texttt{StringEdits} aus der Sequenz derart zu übersetzen (hierbei muss auf die korrekte Handhabung des Komplements geachtet werden) und jene Übersetzungen dann zu concatenieren.
158 167
159Wir definieren zunächst die \emph{Wirkung} eines DFST auf einen festen String als eine Abbildung `state -> (state, String)`, die den aktuellen Zustand vorm Parsen des Strings auf den Zustand danach und die (womöglich leere) Ausgabe schickt. 168Wir definieren zunächst die \emph{Wirkung} eines DFST auf einen festen String als eine Abbildung \texttt{state -> (Seq output, Maybe state)}, die den aktuellen Zustand vor dem Parsen des Strings auf den Zustand danach und die (womöglich leere) Ausgabe schickt.
169Wir annotieren Wirkungen zudem mit dem konsumierten String.
160Diese Wirkungen bilden einen Monoiden analog zu Endomorphismen, wobei die Resultat-Strings concateniert werden. 170Diese Wirkungen bilden einen Monoiden analog zu Endomorphismen, wobei die Resultat-Strings concateniert werden.
161 171
162Die Unterliegende Idee ist nun im Komplement der edit-lens eine Liste von Wirkungen (eine für jedes Zeichen der Eingabe des DFSTs) und einen Cache der monoidalen Summen aller kontinuirlichen Teillisten zu halten.
163Da wir wissen welche Stelle im input-String von einem gegebenen edit betroffen ist können wir, anhand der Wirkung des Teilstücks bis zu jener Stelle, den output-String in einen durch den edit unveränderten Prefix und einen womöglich betroffenen Suffix unterteilen.
164Die Wirkung ab der betroffenen Stelle im input-String können wir also Komposition der Wirkung der durch den edit betroffenen Stelle und derer aller Zeichen danach bestimmen.
165Nun gilt es nur noch die Differenz (als `StringEdits`) des vorherigen Suffixes im output-String und des aus der gerade berechneten Wirkung Bestimmten zu bestimmen.
166
167
168% Für die Rückrichtung bietet es sich an eine Art primitive Invertierung des DFSTs zu berechnen.
169% Gegeben den aktuellen DFST $A$ möchten wir einen anderen $A^{-1}$ finden, sodass gilt:
170
171% \begin{itemize}
172% \item $A^{-1}$ akzeptiert einen String $s^{-1}$ (endet seinen Lauf in einem finalen Zustand) gdw. es einen String $s$ gibt, der unter $A$ die Ausgabe $s^{-1}$ produziert.
173% \item Wenn $A^{-1}$ einen String $s^{-1}$ akzeptiert so produziert die resultierende Ausgabe $s$ unter $A$ die Ausgabe $s^{-1}$.
174% \end{itemize}
175
176% Kann nicht funktionieren, denn $A^{-1}$ ist notwendigerweise nondeterministisch. Wird $A^{-1}$ dann zu einem DFST forciert (durch arbiträre Wahl einer Transition pro Zustand) gehen Informationen verloren—$A^{-1}$ produziert nicht den minimale edit auf dem input string (in der Tat beliebig schlecht) für einen gegeben edit auf dem output string.
177
178% Stelle im bisherigen Lauf isolieren, an der edit im output-string passieren soll, breitensuche auf pfaden, die sich von dieser stelle aus unterscheiden?
179% Gegeben einen Pfad und eine markierte Transition, finde Liste aller Pfade aufsteigend sortiert nach Unterschied zu gegebenem Pfad, mit Unterschieden "nahe" der markierten Transition zuerst — zudem jeweils edit auf dem Eingabestring
180% Einfacher ist Breitensuche ab `stInitial` und zunächst diff auf eingabe-strings.
181
182\begin{code} 172\begin{code}
183
184data DFSTAction state input output = DFSTAction 173data DFSTAction state input output = DFSTAction
185 { runDFSTAction :: state -> (state, Seq output) 174 { runDFSTAction :: state -> (Seq output, Maybe state)
186 , dfstaConsumes :: Seq input 175 , dfstaConsumes :: Seq input
187 } 176 }
188 177
189instance Monoid (DFSTAction state input output) where 178instance Monoid (DFSTAction state input output) where
190 mempty = DFSTAction (\x -> (x, Seq.empty)) Seq.empty 179\end{code}
180\begin{comment}
181\begin{code}
182 mempty = DFSTAction (\x -> (Seq.empty, Just x)) Seq.empty
191 DFSTAction f cf `mappend` DFSTAction g cg = DFSTAction 183 DFSTAction f cf `mappend` DFSTAction g cg = DFSTAction
192 { runDFSTAction = \s -> let ((f -> (s', out')), out) = g s in (s', out <> out') 184 { runDFSTAction = \x ->
185 let (outG, x') = g x
186 (outF, x'') = maybe (mempty, Nothing) f x'
187 in (outG <> outF, x'')
193 , dfstaConsumes = cg <> cf 188 , dfstaConsumes = cg <> cf
194 } 189 }
190\end{code}
191\end{comment}
192\begin{code}
195 193
196type DFSTComplement state input output = Compositions (DFSTAction state input output) 194type DFSTComplement state input output = Compositions (DFSTAction state input output)
197 195
198runDFSTAction' :: DFSTComplement state input output -> state -> (state, Seq output) 196runDFSTAction' :: DFSTComplement state input output -> state -> (Seq output, Maybe state)
199runDFSTAction' = runDFSTAction . Comp.composed 197runDFSTAction' = runDFSTAction . Comp.composed
200 198
201dfstaConsumes' :: DFSTComplement state input output -> Seq input 199dfstaConsumes' :: DFSTComplement state input output -> Seq input
202dfstaConsumes' = dfstaConsumes . Comp.composed 200dfstaConsumes' = dfstaConsumes . Comp.composed
203 201
204dfstaProduces :: DFST state input output -> DFSTComplement state input output -> Seq output 202dfstaProduces :: DFSTComplement state input output -> state -> Seq output
205dfstaProduces DFST{..} = snd . flip runDFSTAction' stInitial 203dfstaProduces = fmap fst . runDFSTAction'
204\end{code}
206 205
207type Debug state input output = (Show state, Show input, Show output) 206Die Unterliegende Idee von $\Rrightarrow$ ist nun im Komplement der edit-lens eine Liste von Wirkungen (eine für jedes Zeichen der Eingabe des DFSTs) und einen Cache der monoidalen Summen aller kontinuirlichen Teillisten zu halten.
208 207
209type LState state input output = (Natural, (state, Maybe (input, Natural))) 208Wir können die alte DFST-Wirkung zunächst anhand des Intervalls indem der input-String von allen gegebenen edits betroffen ist in einen unveränderten Prefix und einen womöglich betroffenen Suffix unterteilen.
209
210Da wir wissen welche Stelle im input-String vom ersten gegebenen edit betroffen ist können wir, anhand der Wirkung des Teilstücks bis zu jener Stelle, den betroffenen Suffix wiederum teilen.
211Die Wirkung ab der betroffenen Stelle im input-String können wir als Komposition der Wirkung der durch den edit betroffenen Stelle und derer aller Zeichen danach bestimmen.
212Nun gilt es nur noch die Differenz (als `StringEdits`) des vorherigen Suffixes im output-String und des aus der gerade berechneten Wirkung zu bestimmen, wir bedienen uns hierzu dem Unix Standard-Diff-Algorithmus zwischen der ursprünglichen Ausgabe und dem Ergebnis der Iteration des Verfahrens auf alle gegebenen edits.
213
214Für die asymmetrische edit-lens entgegen der DFST-Richtung $\Lleftarrow$ verwenden wir Breitensuche über die Zustände des DFST innerhalb eines iterative vergrößerten Intervalls:
215
216Wir bestimmen zunächst (`affected`) eine obere Schranke an das Intervall in dem der Ausgabe-String vom edit betroffen ist und generieren eine von dort quadratisch wachsende Serie von Intervallen.
217
218Für jedes Intervall ("lokalere" Änderungen werden präferiert) schränken wir zunächst den DFST (zur einfachereren Implementierung in seiner Darstellung als FST) vermöge \texttt{restrictOutput} derart ein, dass nur die gewünschte Ausgabe produziert werden kann.
210 219
211dfstLens :: forall state input output. (Ord state, Ord input, Ord output, Debug state input output) => DFST state input output -> EditLens (DFSTComplement state input output) (StringEdits input) (StringEdits output) 220Wir betrachten dann in jedem Schritt (beginnend mit dem initialen Zustand des DFST) alle ausgehenden Transitionen und ziehen hierbei jene vor, die im vorherigen Lauf (gespeichert im Komplement der edit-lens), ebenfalls genommen wurden.
221Abweichungen vom im Komplement gespeicherten Lauf lassen wir nur innerhalb des betrachteten Intervalls zu und wählen in diesem Fall einen Edit auf der Eingabe, der die gewählte Abweichung produziert.
222Es wird zudem, wie für Breitensuche üblich, jeder besuchte Zustand markiert und ausgehende Transitionen nicht ein zweites mal betrachtet.
223
224Erreichen wir einen finalen Zustand (wegen der Einschränkung des DFSTs wurde dann auch genau die gewünschte Ausgabe produziert), so fügen wir an die gesammelten Eingabe-edits eine Serie von deletions an, die den noch nicht konsumierten suffix der Eingabe verwerfen und brechen die Suche unter Rückgabe der Eingabe-edits und des neuen Laufs ab.
225
226In Haskell formulieren wir das vorzeitige Abbrechen der Suche indem wir eine vollständige Liste von Rückgabe-Kandidaten konstruieren und dann immer ihr erstes Element zurück geben.
227Wegen der verzögerten Auswertungsstrategie von Haskell wird auch tatsächlich nur der erste Rückgabe-Kandidat konstruiert.
228
229\begin{comment}
230\begin{code}
231type LState state input output = (Natural, (state, Maybe (input, Natural)))
232\end{code}
233\end{comment}
234\begin{code}
235dfstLens :: forall state input output. (Ord state, Ord input, Ord output, Show state, Show input, Show output) => DFST state input output -> EditLens (DFSTComplement state input output) (StringEdits Natural input) (StringEdits Natural output)
236\end{code}
237\begin{comment}
238\begin{code}
212dfstLens dfst@DFST{..} = EditLens ground propR propL 239dfstLens dfst@DFST{..} = EditLens ground propR propL
213 where 240 where
214 ground :: DFSTComplement state input output 241 ground :: DFSTComplement state input output
215 ground = Comp.fromList [] 242 ground = mempty
216 243
217 propR :: (DFSTComplement state input output, StringEdits input) -> (DFSTComplement state input output, StringEdits output) 244 propR :: (DFSTComplement state input output, StringEdits Natural input) -> (DFSTComplement state input output, StringEdits Natural output)
218 propR (c, SEFail) = (c, SEFail) 245 propR (c, SEFail) = (c, SEFail)
219 propR (c, StringEdits Seq.Empty) = (c, mempty) 246 propR (c, StringEdits Seq.Empty) = (c, mempty)
220 propR (c, StringEdits (es :> e)) 247 propR (c, es'@(StringEdits (es :> e)))
221 | fst (runDFSTAction' c' stInitial) `Set.member` stAccept = (c', es' <> es'') 248 | (_, Just final) <- runDFSTAction' c' stInitial
222 | otherwise = (c', SEFail) 249 , final `Set.member` stAccept
250 = (c', rEs)
251 | otherwise
252 = (c, SEFail)
223 where 253 where
254 Just int = affected es'
255 (cAffSuffix, cAffPrefix) = Comp.splitAt (Comp.length c - fromIntegral (Int.inf int)) c
224 (cSuffix, cPrefix) = Comp.splitAt (Comp.length c - (e ^. sePos . from enum)) c 256 (cSuffix, cPrefix) = Comp.splitAt (Comp.length c - (e ^. sePos . from enum)) c
225 cSuffix' 257 cSuffix'
226 | Delete _ <- e = Comp.take (pred $ Comp.length cSuffix) cSuffix -- TODO unsafe 258 | Delete _ <- e
259 , Comp.length cSuffix > 0 = Comp.take (pred $ Comp.length cSuffix) cSuffix
227 | Insert _ nChar <- e = cSuffix <> Comp.singleton (DFSTAction (\x -> runDFST' dfst x (pure nChar) Seq.empty) (Seq.singleton nChar)) 260 | Insert _ nChar <- e = cSuffix <> Comp.singleton (DFSTAction (\x -> runDFST' dfst x (pure nChar) Seq.empty) (Seq.singleton nChar))
228 (pState, pOutput) = runDFSTAction' cPrefix stInitial 261 | otherwise = Comp.singleton $ DFSTAction (\_ -> (Seq.empty, Nothing)) Seq.empty
229 (_, sOutput ) = runDFSTAction' cSuffix pState 262 (c', _) = propR (cSuffix' <> cPrefix, StringEdits es)
230 (_, sOutput') = runDFSTAction' cSuffix' pState 263 (cAffSuffix', _) = Comp.splitAt (Comp.length c' - Comp.length cAffPrefix) c'
231 (c', es') = propR (cSuffix' <> cPrefix, StringEdits es) 264 (_, Just pFinal) = runDFSTAction' cPrefix stInitial
232 es'' = strDiff sOutput sOutput' & stringEdits . sePos . from enum +~ Seq.length pOutput 265 rEs = strDiff (fst $ runDFSTAction' cAffSuffix pFinal) (fst $ runDFSTAction' cAffSuffix' pFinal) & stringEdits . sePos . from enum +~ length (dfstaProduces cAffPrefix stInitial)
233 266
234 267
235 propL :: (DFSTComplement state input output, StringEdits output) -> (DFSTComplement state input output, StringEdits input) 268 propL :: (DFSTComplement state input output, StringEdits Natural output) -> (DFSTComplement state input output, StringEdits Natural input)
236 propL (c, StringEdits Seq.Empty) = (c, mempty) 269 propL (c, StringEdits Seq.Empty) = (c, mempty)
237 propL (c, es) = fromMaybe (c, SEFail) $ do 270 propL (c, es) = fromMaybe (c, SEFail) $ do
271 let prevOut = dfstaProduces c stInitial
238 newOut <- prevOut `apply` es 272 newOut <- prevOut `apply` es
239 affected' <- affected es 273 affected' <- affected es
240 let outFST :: FST (LState state input output) input output 274 let outFST :: FST (LState state input output) input output
241 outFST = wordFST newOut `productFST` toFST dfst 275 -- outFST = wordFST newOut `productFST` toFST dfst
276 outFST = restrictOutput newOut $ toFST dfst
277
278 trace x y = flip seq y . unsafePerformIO $ appendFile "lens.log" (x <> "\n\n")
279
242 inflate by int 280 inflate by int
243 | Int.null int = Int.empty 281 | Int.null int = Int.empty
244 | inf >= by = inf - by Int.... sup + by 282 | inf >= by = inf - by Int.... sup + by
@@ -251,53 +289,90 @@ dfstLens dfst@DFST{..} = EditLens ground propR propL
251 max = fromIntegral $ Seq.length newOut 289 max = fromIntegral $ Seq.length newOut
252 all = 0 Int.... max 290 all = 0 Int.... max
253 runCandidates :: Interval Natural -- ^ Departure from complement-run only permitted within interval (to guarantee locality) 291 runCandidates :: Interval Natural -- ^ Departure from complement-run only permitted within interval (to guarantee locality)
254 -> [ ( Seq (LState state input output, Maybe output) -- ^ Computed run 292 -> [ ( Seq (LState state input output, Maybe output) -- ^ Computed run
255 , StringEdits input 293 , StringEdits Natural input
256 , DFSTComplement state input output 294 , DFSTComplement state input output
257 ) 295 )
258 ] 296 ]
259 runCandidates focus = continueRun (Seq.empty, mempty) (c, mempty) 0 297 runCandidates focus = map ((,,) <$> view _1 <*> view _2 <*> view (_3 . _2)) $ go Set.empty [(Seq.empty, mempty, (c, mempty), 0)]
260 where 298 where
261 continueRun :: (Seq (LState state input output, Maybe output), StringEdits input) 299 go _ [] = []
300 go visited (args@(run, edits, compZipper, inP) : alts) =
301 [ (run', finalizeEdits remC inP' edits', compZipper', inP') | (run', edits', compZipper'@(remC, _), inP') <- args : conts, isFinal run' ]
302 ++ go visited' (alts ++ conts)
303 where
304 conts
305 | lastSt <- view _1 <$> Seq.lookup (pred $ Seq.length run) run
306 , lastSt `Set.member` visited = []
307 | otherwise = continueRun edits compZipper inP run
308 visited' = Set.insert (view _1 <$> Seq.lookup (pred $ Seq.length run) run) visited
309
310 isFinal :: Seq (LState state input output, Maybe output) -> Bool
311 -- ^ Is the final state of the run a final state of the DFST?
312 isFinal Seq.Empty = (0, (stInitial, Nothing)) `Set.member` FST.stAccept outFST
313 && (0 Int.... fromIntegral (Seq.length newOut)) `Int.isSubsetOf` focus
314 isFinal (_ :> (lastSt, _)) = lastSt `Set.member` FST.stAccept outFST
315
316 finalizeEdits :: DFSTComplement state input output -- ^ Remaining complement
317 -> Natural -- ^ Input position
318 -> StringEdits Natural input -> StringEdits Natural input
319 finalizeEdits remC inP = mappend . mconcat . replicate (Seq.length $ dfstaConsumes' remC) $ delete inP
320
321 continueRun :: StringEdits Natural input
262 -> (DFSTComplement state input output, DFSTComplement state input output) -- ^ Zipper into complement 322 -> (DFSTComplement state input output, DFSTComplement state input output) -- ^ Zipper into complement
263 -> Natural -- ^ Input position 323 -> Natural -- ^ Input position
264 -> [(Seq (LState state input output, Maybe output), StringEdits input, DFSTComplement state input output)] 324 -> Seq (LState state input output, Maybe output)
265 continueRun (run, inEdits) (c', remC) inP = do 325 -> [ ( Seq (LState state input output, Maybe output)
326 , StringEdits Natural input
327 , (DFSTComplement state input output, DFSTComplement state input output)
328 , Natural
329 )
330 ]
331 -- ^ Nondeterministically make a single further step, continueing a given run
332 continueRun inEdits (c', remC) inP run = do
266 let 333 let
267 pos :: Natural 334 pos :: Natural
268 pos = fromIntegral $ Comp.length c - Comp.length c' 335 -- pos = fromIntegral $ Comp.length c - Comp.length c' -- FIXME: should use length of dfstaProduces
336 pos = fromIntegral . Seq.length $ dfstaProduces remC stInitial
269 (c'', step) = Comp.splitAt (pred $ Comp.length c') c' -- TODO: unsafe? 337 (c'', step) = Comp.splitAt (pred $ Comp.length c') c' -- TODO: unsafe?
270 current :: LState state input output 338 current :: LState state input output
271 current 339 current
272 | Seq.Empty <- run = (0, (stInitial, Nothing)) 340 | Seq.Empty <- run = (0, (stInitial, Nothing))
273 | (_ :> (st, _)) <- run = st 341 | (_ :> (st, _)) <- run = st
274 current' :: state 342 current' :: state
275 current' = let (_, (st, _)) = current
276 in st
277 next' :: state
278 next' = fst . runDFSTAction' step $ current'
279 oldIn :: Maybe input 343 oldIn :: Maybe input
280 oldIn = Seq.lookup 0 $ dfstaConsumes' step 344 (current', oldIn)
345 | (_ :> ((_, (st, _)), _)) <- rest
346 , (_ :> ((_, (_, Just (partialIn, _))), _)) <- partial = (st, Just partialIn)
347 | (_ :> ((_, (_, Just (partialIn, _))), _)) <- partial = (stInitial, Just partialIn)
348 | Seq.Empty <- rest = (stInitial, Seq.lookup 0 $ dfstaConsumes' step)
349 | (_ :> ((_, (st, _)), _)) <- rest = (st, Seq.lookup 0 $ dfstaConsumes' step)
350 where
351 (partial, rest) = Seq.spanr (\((_, (_, inp)), _) -> isJust inp) run
352 next' <- trace (show ("next'", pos, focus, run, (current', oldIn), current, dfstaConsumes' step, runDFST' dfst current' (maybe Seq.empty Seq.singleton oldIn) Seq.empty)) . maybeToList . snd $ runDFST' dfst current' (maybe Seq.empty Seq.singleton oldIn) Seq.empty
353 let
281 outgoing :: LState state input output -> [(LState state input output, Maybe input, Maybe output)] 354 outgoing :: LState state input output -> [(LState state input output, Maybe input, Maybe output)]
282 outgoing current = let go (st, minS) os acc 355 outgoing current = let go (st, minS) outs acc
283 | st == current = ($ acc) $ Set.fold (\(st', moutS) -> (. ((st', minS, moutS) :))) id os 356 | st == current = Set.foldr (\(st', moutS) -> ((st', minS, moutS) :)) acc outs
284 | otherwise = acc 357 | otherwise = acc
285 in Map.foldrWithKey go [] $ FST.stTransition outFST 358 in Map.foldrWithKey go [] $ FST.stTransition outFST
286 isPreferred :: (LState state input output, Maybe input, Maybe output) -> Bool 359 isPreferred :: (LState state input output, Maybe input, Maybe output) -> Bool
287 isPreferred ((_, (st, Nothing)), inS, _) = st == next' && (fromMaybe True $ (==) <$> oldIn <*> inS) 360 isPreferred ((_, (st, Nothing)), _, _) = st == next'
288 isPreferred (st, _, _) = any isPreferred $ outgoing st -- By construction of `outFST`, `outgoing st` is a singleton 361 isPreferred (st@(_, (_, Just (inS , _))), _, _) = maybe True (== inS) oldIn && any isPreferred (outgoing st) -- By construction of `outFST`, `outgoing st` is a singleton in this case
289 (preferred, alternate) = partition isPreferred $ outgoing current 362 (preferred, alternate) = partition isPreferred $ outgoing current
290 assocEdit :: (LState state input output, Maybe input, Maybe output) -- ^ Transition 363 assocEdit :: (LState state input output, Maybe input, Maybe output) -- ^ Transition
291 -> [ ( (DFSTComplement state input output, DFSTComplement state input output) -- ^ new `(c', remC)`, i.e. complement-zipper `(c', remC)` but with edit applied 364 -> [ ( (DFSTComplement state input output, DFSTComplement state input output) -- ^ new `(c', remC)`, i.e. complement-zipper `(c', remC)` but with edit applied
292 , StringEdits input 365 , StringEdits Natural input
293 , Natural 366 , Natural
294 ) 367 )
295 ] 368 ]
296 assocEdit (_, Just inS, _) 369 assocEdit (_, Just inS, _)
297 | oldIn == Just inS = [((c'', step <> remC), mempty, succ inP)] 370 | oldIn == Just inS = [ ((c'', step <> remC), mempty, succ inP) ]
298 | isJust oldIn = [((c'', altStep inS <> remC), replace inP inS, succ inP), ((c', altStep inS <> remC), insert inP inS, succ inP)] 371 | isJust oldIn = [ ((c', altStep inS <> remC), insert inP inS, succ inP)
299 | otherwise = [((c', altStep inS <> remC), insert inP inS, succ inP)] 372 , ((c'', altStep inS <> remC), replace inP inS, succ inP)
300 assocEdit (_, Nothing, _) = [((c', remC), mempty, inP)] -- TODO: is this correct? 373 ]
374 | otherwise = [ ((c', altStep inS <> remC), insert inP inS, succ inP) ]
375 assocEdit (_, Nothing, _) = [((c', remC), mempty, inP)]
301 altStep :: input -> DFSTComplement state input output 376 altStep :: input -> DFSTComplement state input output
302 altStep inS = Comp.singleton DFSTAction{..} 377 altStep inS = Comp.singleton DFSTAction{..}
303 where 378 where
@@ -306,7 +381,7 @@ dfstLens dfst@DFST{..} = EditLens ground propR propL
306 options 381 options
307 | pos `Int.member` focus = preferred ++ alternate 382 | pos `Int.member` focus = preferred ++ alternate
308 | otherwise = preferred 383 | otherwise = preferred
309 choice@(next, inS, outS) <- options 384 choice@(next, inS, outS) <- trace (unlines $ show (pretty outFST) : map show options) options
310 ((c3, remC'), inEdits', inP') <- assocEdit choice 385 ((c3, remC'), inEdits', inP') <- assocEdit choice
311 -- let 386 -- let
312 -- -- | Replace prefix of old complement to reflect current candidate 387 -- -- | Replace prefix of old complement to reflect current candidate
@@ -317,27 +392,70 @@ dfstLens dfst@DFST{..} = EditLens ground propR propL
317 -- fin 392 -- fin
318 -- | (trans, inEs, newComplement) <- acc = (trans, dropSuffix <> inEs, newComplement) 393 -- | (trans, inEs, newComplement) <- acc = (trans, dropSuffix <> inEs, newComplement)
319 let 394 let
320 acc = (run :> (next, outS), inEdits' <> inEdits) 395 trans = run :> (next, outS)
321 dropSuffix = mconcat (replicate (Seq.length $ dfstaConsumes' c3) $ delete inP') 396 inEs = inEdits' <> inEdits
322 fin 397 -- dropSuffix = mconcat (replicate (Seq.length $ dfstaConsumes' c3) $ delete inP')
323 | (trans, inEs) <- acc = (trans, dropSuffix <> inEs, remC') 398 -- fin
324 bool id (fin :) (next `Set.member` FST.stAccept outFST) $ continueRun acc (c3, remC') inP' 399 -- | (trans, inEs) <- acc = (trans, dropSuffix <> inEs, remC')
400 -- bool id (over _BFS $ cons fin) (next `Set.member` FST.stAccept outFST) $ continueRun acc (c3, remC') inP'
401 return (trans, inEs, (c3, remC'), inP')
325 402
326 -- Properties of the edits computed are determined mostly by the order candidates are generated below 403 -- Properties of the edits computed are determined mostly by the order candidates are generated below
327 -- (_, inEs, c') <- (\xs -> foldr (\x f -> x `seq` f) listToMaybe xs $ xs) $ traceShowId fragmentIntervals >>= (\x -> (\y@(y1, y2, _) -> traceShow (y1, y2) y) <$> runCandidates x) 404 -- (_, inEs, c') <- (\xs -> foldr (\x f -> x `seq` f) listToMaybe xs $ xs) $ traceShowId fragmentIntervals >>= (\x -> (\y@(y1, y2, _) -> traceShow (y1, y2) y) <$> runCandidates x)
328 405
329 (_, inEs, c') <- listToMaybe $ runCandidates =<< fragmentIntervals 406 fmap ((,) <$> view _3 <*> view _2) . listToMaybe $ runCandidates =<< fragmentIntervals
330
331 return (c', inEs)
332 where
333 (_, prevOut) = runDFSTAction' c stInitial
334 407
335strDiff :: forall sym. Eq sym => Seq sym -> Seq sym -> StringEdits sym 408strDiff :: forall sym pos. (Eq sym, Integral pos) => Seq sym -> Seq sym -> StringEdits pos sym
336-- ^ @strDiff a b@ calculates a set of edits, which, when applied to @a@, produce @b@ 409-- ^ @strDiff a b@ calculates a set of edits, which, when applied to @a@, produce @b@
337strDiff a b = snd . foldr toEdit (0, mempty) $ (getDiff `on` toList) a b 410strDiff a b = snd . foldl toEdit (0, mempty) $ (getDiff `on` toList) a b
411 where
412 toEdit :: (pos, StringEdits pos sym) -> Diff sym -> (pos, StringEdits pos sym)
413 toEdit (n, es) (Diff.Both _ _) = (succ n, es)
414 toEdit (n, es) (Diff.First _ ) = (n, delete n <> es)
415 toEdit (n, es) (Diff.Second c) = (succ n, insert n c <> es)
416\end{code}
417\end{comment}
418
419Um eine obere Schranke an das von einer Serie von edits betroffene Intervall zu bestimmen ordnen wir zunächst jeder von mindestens einem atomaren edit betroffenen Position $n$ im Eingabe-Wort einen $\text{offset}_n = \text{\# deletions} - \text{\# inserts}$ zu.
420Das gesuchte Intervall ist nun $(\text{minK}, \text{maxK})$, mit $\text{minK}$ der Position im Eingabe-Wort mit niedrigstem $\text{offset}$ und $\text{maxK}$ die Position im Eingabe-Wort mit höchstem $\text{offset}$, $\text{maxK}^\prime$, modifiziert um das Maximum aus $\{ 0 \} \cup \{ \text{maxK}_n \colon n \in \{ 0 \ldots \text{maxK}^\prime \} \}$ wobei $\text{maxK}_n = -1 \cdot (n + \text{offset}_n)$ an Position $n$ ist.
421
422\begin{code}
423affected :: forall char. StringEdits Natural char -> Maybe (Interval Natural)
424-- ^ For a given set of edits @es@ return the interval @i = a ... b@ such that for any given string @str@ of sufficient length the following holds:
425--
426-- - For all @n :: Natural@: @n < a ==> str ! n == (str `apply` es) ! n@
427-- - There exists a @k :: Integer@ such that for all @n :: Integer@: @n > b ==> str ! (n + k) == (str `apply` es) ! n@
428--
429-- Intuitively: for any character @c@ of the new string @str `apply` es@ there exists a corresponding character in @str@ (offset by either 0 or a constant shift @k@) if the index of @c@ is /not/ contained in @affected es@.
430\end{code}
431\begin{comment}
432\begin{code}
433affected SEFail = Nothing
434affected (StringEdits es) = Just . toInterval $ go es Map.empty
338 where 435 where
339 toEdit :: Diff sym -> (Natural, StringEdits sym) -> (Natural, StringEdits sym) 436 toInterval :: Map Natural Integer -> Interval Natural
340 toEdit (Diff.Both _ _) (n, es) = (succ n, es) 437 toInterval map
341 toEdit (Diff.First _ ) (n, es) = (n, delete n <> es) 438 | Just (((minK, _), _), ((maxK, _), _)) <- (,) <$> Map.minViewWithKey map <*> Map.maxViewWithKey map
342 toEdit (Diff.Second c) (n, es) = (succ n, insert n c <> es) 439 = let
440 maxV' = maximum . (0 :) $ do
441 offset <- [0..maxK]
442 v <- maybeToList $ Map.lookup (maxK - offset) map
443 v' <- maybeToList . fmap fromInteger $ negate v <$ guard (v <= 0)
444 guard $ v' >= succ offset
445 return $ v' - offset
446 in (minK Int.... maxK + maxV')
447 | otherwise
448 = Int.empty
449 go :: Seq (StringEdit Natural char) -> Map Natural Integer -> Map Natural Integer
450 go Seq.Empty offsets = offsets
451 go (es :> e) offsets = go es offsets'
452 where
453 p = e ^. sePos
454 -- p' = fromIntegral $ Map.foldrWithKey (\k o p -> bool (fromIntegral p) (o + p) $ k < fromIntegral p) (fromIntegral p) offsets
455 offsets' = Map.alter (Just . myOffset . fromMaybe 0) p offsets
456 myOffset :: Integer -> Integer
457 myOffset
458 | Insert _ _ <- e = pred
459 | Delete _ <- e = succ
343\end{code} 460\end{code}
461\end{comment}
diff --git a/edit-lens/src/Control/Edit.lhs b/edit-lens/src/Control/Edit.lhs
index 19fe336..8c4f045 100644
--- a/edit-lens/src/Control/Edit.lhs
+++ b/edit-lens/src/Control/Edit.lhs
@@ -16,7 +16,7 @@ Ein Modul $M$ ist eine \emph{partielle Monoidwirkung} zusammen mit einem schwach
16 16
17und einem Element $\init_M \in \Dom M$, sodass gilt: 17und einem Element $\init_M \in \Dom M$, sodass gilt:
18 18
19$$ \forall m \in \Dom M \ \exists \partial m \in \partial M \colon m = \init_M \cdot \partial m$$ 19$$\forall m \in \Dom M \ \exists \partial m \in \partial M \colon m = \init_M \cdot \partial m$$
20 20
21Wir führen außerdem eine Abbildung $(\init_M \cdot)^{-1} \colon \Dom M \to \partial m$ ein, die ein $m$ auf ein arbiträr gewähltes $\partial m$ abbildet für das $\init_M \cdot \partial m = m$ gilt. 21Wir führen außerdem eine Abbildung $(\init_M \cdot)^{-1} \colon \Dom M \to \partial m$ ein, die ein $m$ auf ein arbiträr gewähltes $\partial m$ abbildet für das $\init_M \cdot \partial m = m$ gilt.
22 22
@@ -24,6 +24,7 @@ In Haskell charakterisieren wir Moduln über ihren Monoid, d.h. die Wahl des Mon
24Eine Repräsentierung als Typklasse bietet sich an: 24Eine Repräsentierung als Typklasse bietet sich an:
25 25
26\begin{code} 26\begin{code}
27-- `apply` binds one level weaker than monoid composition `(<>)`
27infix 5 `apply` 28infix 5 `apply`
28 29
29class Monoid m => Module m where 30class Monoid m => Module m where
@@ -42,11 +43,12 @@ class Monoid m => Module m where
42 43
43infixl 5 `apply'` 44infixl 5 `apply'`
44apply' :: Module m => Maybe (Domain m) -> m -> Maybe (Domain m) 45apply' :: Module m => Maybe (Domain m) -> m -> Maybe (Domain m)
46-- ^ `apply` under `Maybe`s monad-structure
45apply' md e = flip apply e =<< md 47apply' md e = flip apply e =<< md
46\end{code} 48\end{code}
47\end{defn} 49\end{defn}
48 50
49Wir weichen von der originalen Definition von Moduln aus \cite{hofmann2012edit} darin ab, dass wir für das ausgezeichnete Element $\init_X$ des Trägers explizit (und konstruktiv) fordern, dass es ein schwach-initiales Element bzgl. der Monoidwirkung sei. 51Wir weichen von der originalen Definition von Moduln aus \cite{hofmann2012edit} darin ab, dass wir für das ausgezeichnete Element $\init_X$ des Trägers explizit (und konstruktiv\footnote{$(\init_M \cdot)^{-1}$}) fordern, dass es ein schwach-initiales Element bzgl. der Monoidwirkung sei.
50 52
51\begin{comment} 53\begin{comment}
52\begin{defn}[Modulhomomorphismen] 54\begin{defn}[Modulhomomorphismen]
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-}
8module Control.FST 9module 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
18import Data.Map.Strict (Map, (!?)) 21import Data.Map.Lazy (Map, (!?), (!))
19import qualified Data.Map.Strict as Map 22import qualified Data.Map.Lazy as Map
20 23
21import Data.Set (Set) 24import Data.Set (Set)
22import qualified Data.Set as Set 25import qualified Data.Set as Set
@@ -24,7 +27,7 @@ import qualified Data.Set as Set
24import Data.Sequence (Seq) 27import Data.Sequence (Seq)
25import qualified Data.Sequence as Seq 28import qualified Data.Sequence as Seq
26 29
27import Data.Maybe (mapMaybe, fromMaybe, isJust, fromJust) 30import Data.Maybe (mapMaybe, fromMaybe, isJust, fromJust, isNothing)
28 31
29import Numeric.Natural 32import Numeric.Natural
30 33
@@ -35,12 +38,28 @@ import Control.Monad.State.Strict
35import Text.PrettyPrint.Leijen (Pretty(..)) 38import Text.PrettyPrint.Leijen (Pretty(..))
36import qualified Text.PrettyPrint.Leijen as PP 39import qualified Text.PrettyPrint.Leijen as PP
37 40
38data FST state input output = FST 41\end{code}
42\end{comment}
43
44\begin{defn}[Finite state transducers]
45Unter 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
47Semantisch 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
49In Haskell lockern wir die Anforderung, dass die Ein- und Ausgabe-Alphabete endlich sein müssen und annotieren sie nur im Typsystem.
50Zudem speichern wir die Transitionsrelation als multimap um effiziente lookups von Zustand-Eingabe-Paaren zu ermöglichen.
51
52\begin{code}
53dFSeata 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}
44instance (Show state, Show input, Show output) => Pretty (FST state input output) where 63instance (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
62runFST :: forall input output state. (Ord input, Ord output, Ord state) => FST state input output -> Seq input -> [Seq output] 83Wir definieren die Auswertung von finite state transducers induktiv indem wir zunächst angeben wie ein einzelner Auswertungs-Schritt erfolgt.
63runFST = fmap (map $ catMaybes . fmap (view _2) . view _2) . runFST' 84
64 where 85Hierzu kommentieren wir die Haskell-Implementierung eines Auswertungs-Schritts.
65 catMaybes = fmap fromJust . Seq.filter isJust 86Notwendigerweise ist die Auswertung eines FSTs nicht deterministisch, wir produzieren daher eine Liste von möglichen Resultaten in keiner besonderen Reihenfolge.
87
88\begin{code}
89step :: 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
94step FST{..} Nothing inS = (\s -> (inS, s, Nothing)) <$> Set.toList stInitial
95\end{code}
96Ist kein vorheriger Schritt erfolgt so wählen wir einen initialen Zustand, konsumieren keine Eingabe, und produzieren keine Ausgabe.
97
98\begin{code}
99step 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}
104Ansonsten wählen wir einen Eintrag aus der Transitionstabelle für den aktuellen Zustand, der entweder keine oder die gegebene Eingabe konsumiert.
105Im Ergebnis geben wir den nächsten Zustand, die Ausgabe aus der Transitionstabelle, und ob die Eingabe konsumiert wurde an.
66 106
107\begin{code}
67runFST' :: forall input output state. (Ord input, Ord output, Ord state) 108runFST' :: 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
72runFST' fst Seq.Empty = guardAccept $ (\(_, st, _) -> (st, Seq.Empty)) <$> step fst Nothing Nothing 113runFST' fst@FST{..} cs = do
73runFST' 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
121Um alle möglichen Läufe auf einer gegebenen Eingabe zu berechnen wenden wir
122rekursiv \texttt{step} auf den letzten Zustand des Laufs (und der verbleibenden
123Eingabe) an bis keine Eingabe verbleibt und der letzte Zustand in der Menge der
124akzeptierenden 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
149Es ist gelegentlich nützlich nur die möglichen Ausgaben eines FST auf gegebener
150Eingabe zu bestimmen, wir führen eine Hilfsfunktion auf Basis von
151{\ttfamily runFST'} ein:
152
153\begin{code}
154runFST :: 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}
159runFST = 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
165Wir können das Produkt zweier FSTs definieren.
166Intuitiv 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
168Hierfü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
99step :: 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
104step FST{..} Nothing inS = (\s -> (inS, s, Nothing)) <$> Set.toList stInitial
105step 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}
188productFST :: 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
111wordFST :: 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}
113wordFST outs = FST 198productFST 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
218Es ist später erforderlich einen FST derart einzuschränken, dass er eine gegebene Ausgabe produziert.
219
220Hierzu nehmen wir das FST-Produkt mit einem FST, der, ungeachtet der Eingabe, immer die gegebene Ausgabe produziert.
221Da 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
223Zur 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).
225Weiter ist $0$ initial und $\text{length}(\text{Ausgabe})$ der einzige akzeptierende Endzustand.
226
227\begin{code}
228wordFST :: 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}
234wordFST 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
126productFST :: 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 254Da \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. 257restrictOutput :: 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}
132productFST 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) 263restrictOutput 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}
152restrictFST :: forall state input output. (Ord state, Ord input, Ord output) => Set state -> FST state input output -> FST state input output 287restrictFST :: 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
154restrictFST sts FST{..} = FST 289restrictFST sts FST{..} = FST
@@ -170,7 +305,7 @@ liveFST :: forall state input output. (Ord state, Ord input, Ord output, Show st
170liveFST fst@FST{..} = flip execState Set.empty $ mapM_ (depthSearch Set.empty) stInitial 305liveFST 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}
diff --git a/edit-lens/src/Control/Lens/Edit.lhs b/edit-lens/src/Control/Lens/Edit.lhs
index 5a60536..5a106c8 100644
--- a/edit-lens/src/Control/Lens/Edit.lhs
+++ b/edit-lens/src/Control/Lens/Edit.lhs
@@ -1,3 +1,4 @@
1\begin{comment}
1\begin{code} 2\begin{code}
2module Control.Lens.Edit 3module Control.Lens.Edit
3 ( Module(..) 4 ( Module(..)
@@ -8,9 +9,10 @@ module Control.Lens.Edit
8 9
9import Control.Edit 10import Control.Edit
10\end{code} 11\end{code}
12\end{comment}
11 13
12\begin{defn}[Zustandsbehaftete Monoidhomomorphismen] 14\begin{defn}[Zustandsbehaftete Monoidhomomorphismen]
13Mit einer Menge von Komplementen $C$ und Monoiden $M$ und $N$ nennen wir eine partielle Funktion $\psi \colon C \times M \to C \times N$ einen zustandsbehafteten Monoidhomomorphismus wenn sie den folgenden Ansprüchen genügt: 15Gegeben eine Menge von Komplementen $C$ und Monoiden $M$ und $N$ nennen wir eine partielle Funktion $\psi \colon C \times M \to C \times N$ einen zustandsbehafteten Monoidhomomorphismus wenn sie den folgenden Ansprüchen genügt:
14 16
15\begin{itemize} 17\begin{itemize}
16 \item $\forall c \in C \colon \psi(1_M, c) = (1_N, c)$ 18 \item $\forall c \in C \colon \psi(1_M, c) = (1_N, c)$
@@ -26,7 +28,7 @@ type StateMonoidHom s m n = (s, m) -> (s, n)
26\end{defn} 28\end{defn}
27 29
28\begin{defn}[edit-lenses] 30\begin{defn}[edit-lenses]
29Für Moduln $M$ und $N$ besteht eine symmetrische edit-lens zwischen $M$ und $N$ aus zwei zustandsbehafteten Monoidhomomorphismen $\Rrightarrow \colon C \times \partial M \to C \times \partial N$ und $\Lleftarrow \colon C \time \partial N \to C \times \partial M$, mit kompatiblem Komplement $C$, einem ausgezeichneten Element $\ground_C$ und einer \emph{Konsistenzrelation} $K \subset \Dom M \times C \times \Dom N$ sodass gilt: 31Für Moduln $M$ und $N$ besteht eine symmetrische edit-lens zwischen $M$ und $N$ aus zwei zustandsbehafteten Monoidhomomorphismen $\Rrightarrow \colon C \times \partial M \to C \times \partial N$ und $\Lleftarrow \colon C \times \partial N \to C \times \partial M$, mit kompatiblem Komplement $C$, einem ausgezeichneten Element $\ground_C$ und einer \emph{Konsistenzrelation} $K \subset \Dom M \times C \times \Dom N$ sodass gilt:
30 32
31\begin{itemize} 33\begin{itemize}
32 \item $(\init_M, \ground_C, \init_N) \in K$ 34 \item $(\init_M, \ground_C, \init_N) \in K$
@@ -41,7 +43,7 @@ Für Moduln $M$ und $N$ besteht eine symmetrische edit-lens zwischen $M$ und $N$
41 43
42Wir schreiben auch nur \emph{edit-lens} für den symmetrischen Fall\footnote{Für den asymmetrischen Fall siehe \cite{johnson2016unifying}}. 44Wir schreiben auch nur \emph{edit-lens} für den symmetrischen Fall\footnote{Für den asymmetrischen Fall siehe \cite{johnson2016unifying}}.
43 45
44In Haskell erwähnen wir die Konsistenzrelation nicht in der Erwartung, dass $\Rrightarrow$ und $\Lleftarrow$ nur auf konsistente Zustände angewandt werden (und somit auch entweder einen konsistenten Zustand erzeugen oder nichtt definiert sind): 46In Haskell erwähnen wir die Konsistenzrelation nicht in der Erwartung, dass $\Rrightarrow$ und $\Lleftarrow$ nur auf konsistente Zustände angewandt werden (und somit auch entweder einen konsistenten Zustand erzeugen oder nicht definiert sind):
45 47
46\begin{code} 48\begin{code}
47data EditLens c m n where 49data EditLens c m n where
@@ -74,7 +76,7 @@ Für Typen $n$ und $m$ ist eine \emph{lens} $\ell$ von $n$ in $m$ eine Abbildung
74 76
75$$ \forall f \, \text{Funktor} \colon \left ( \ell \colon \left ( m \to f(m) \right ) \to \left ( n \to f(n) \right ) \right )$$ 77$$ \forall f \, \text{Funktor} \colon \left ( \ell \colon \left ( m \to f(m) \right ) \to \left ( n \to f(n) \right ) \right )$$
76 78
77Durch geschickte Wahl des Funktors\footnote{\texttt{Const} bzw. \texttt{Identity}} $f$ können dann $\searrow \colon m \to n$ und $\nearrow \colon (m \to m) \to (n \to n)$ rekonstruiert werden oder verwandte Strukturen (folds, traversals, …) konstruiert werden. 79Durch geschickte Wahl des Funktors\footnote{\texttt{Const} bzw. \texttt{Identity}} $f$ können dann $\searrow \colon m \to n$ und $\nearrow \colon (m \to m) \to (n \to n)$ oder verwandte Strukturen (folds, traversals, …) konstruiert werden.
78\end{defn} 80\end{defn}
79 81
80Es liegt nun nahe $\nearrow \colon (m \to m) \to (n \to n)$ mit $\Rrightarrow \colon \partial m \to \partial n$ zu identifizieren. 82Es liegt nun nahe $\nearrow \colon (m \to m) \to (n \to n)$ mit $\Rrightarrow \colon \partial m \to \partial n$ zu identifizieren.
diff --git a/edit-lens/test/Control/DFST/LensTest.hs b/edit-lens/test/Control/DFST/LensTest.hs
new file mode 100644
index 0000000..46a1896
--- /dev/null
+++ b/edit-lens/test/Control/DFST/LensTest.hs
@@ -0,0 +1,35 @@
1module Control.DFST.LensTest where
2
3import Prelude hiding (init)
4
5import Control.DFST
6import Control.DFST.Lens
7import Control.FST hiding (stInitial, stTransition, stAccept)
8
9import Data.Set (Set)
10import qualified Data.Set as Set
11
12import Data.Map.Strict (Map)
13import qualified Data.Map.Strict as Map
14
15import Data.Sequence (Seq)
16import qualified Data.Sequence as Seq
17
18import Data.Maybe (maybeToList)
19
20import Test.Tasty
21import Test.Tasty.Hedgehog
22import Test.Tasty.HUnit hiding (assert)
23
24import Hedgehog
25import qualified Hedgehog.Gen as G
26import qualified Hedgehog.Range as R
27
28import Numeric.Natural
29
30import Control.DFSTTest
31
32hprop_applyDivInit :: Property
33hprop_applyDivInit = property $ do
34 word <- Seq.fromList <$> forAll genWord
35 init @(StringEdits Natural) `apply` (divInit word :: StringEdits Natural) === Just word
diff --git a/edit-lens/test/Control/DFSTTest.hs b/edit-lens/test/Control/DFSTTest.hs
new file mode 100644
index 0000000..4d91a03
--- /dev/null
+++ b/edit-lens/test/Control/DFSTTest.hs
@@ -0,0 +1,101 @@
1module Control.DFSTTest where
2
3import Control.DFST
4import Control.FST hiding (stInitial, stTransition, stAccept)
5
6import Data.Set (Set)
7import qualified Data.Set as Set
8
9import Data.Map.Strict (Map)
10import qualified Data.Map.Strict as Map
11
12import Data.Sequence (Seq)
13import qualified Data.Sequence as Seq
14
15import Data.Maybe (maybeToList)
16
17import Test.Tasty
18import Test.Tasty.Hedgehog
19import Test.Tasty.HUnit hiding (assert)
20
21import Hedgehog
22import qualified Hedgehog.Gen as G
23import qualified Hedgehog.Range as R
24
25import Numeric.Natural
26
27import Text.PrettyPrint.Leijen (Pretty(..))
28
29
30dfstId :: Ord a => Set a -> DFST () a a
31dfstId syms = DFST
32 { stInitial = ()
33 , stTransition = Map.fromList
34 [(((), sym), ((), Seq.singleton sym)) | sym <- Set.toList syms]
35 , stAccept = Set.singleton ()
36 }
37
38dfstDouble :: Ord a => Set a -> DFST () a a
39dfstDouble syms = DFST
40 { stInitial = ()
41 , stTransition = Map.fromList
42 [(((), sym), ((), Seq.fromList [sym, sym])) | sym <- Set.toList syms]
43 , stAccept = Set.singleton ()
44 }
45
46dfstRunLengthDecode :: Ord a
47 => Set a
48 -> Natural
49 -> DFST (Maybe Natural) (Either Natural a) a
50dfstRunLengthDecode syms lim = DFST
51 { stInitial = Nothing
52 , stTransition = Map.fromList . concat $
53 [ [((Nothing, Left n), (Just n, Seq.empty)) | n <- [0..lim]]
54 , [((Just n, Right sym), (Nothing, Seq.replicate (fromIntegral n) sym)) | n <- [0..lim], sym <- Set.toList syms]
55 ]
56 , stAccept = Set.singleton Nothing
57 }
58
59genWord :: Gen [Natural]
60genWord = G.list (R.linear 0 1000) . G.integral $ R.linear 0 100
61
62genDFST :: (Ord input, Ord output) => Set input -> Set output -> Gen (DFST Natural input output)
63genDFST inA outA = do
64 states <- G.set (R.linear 1 1000) . G.integral $ R.linear 0 100
65 stInitial <- G.element $ Set.toList states
66 stAccept <- Set.fromList <$> G.subsequence (Set.toList states)
67 stTransition <- fmap Map.fromList . G.list (R.linear 0 1000) . G.small $ do
68 st <- G.element $ Set.toList states
69 input <- G.element $ Set.toList inA
70 st' <- G.element $ Set.toList states
71 output <- fmap Seq.fromList . G.list (R.linear 0 20) . G.element $ Set.toList outA
72 return ((st, input), (st', output))
73 return DFST{..}
74
75
76testDFST :: (Show output, Ord output, Show state, Ord state) => (Set Natural -> DFST state Natural output) -> (Seq Natural -> Seq output) -> Property
77testDFST mkDfst f = property $ do
78 input <- forAll genWord
79 let fst = mkDfst $ Set.fromList input
80 Just (f $ Seq.fromList input) === runDFST fst (Seq.fromList input)
81
82hprop_runDFSTId, hprop_runDFSTDouble :: Property
83hprop_runDFSTId = testDFST dfstId id
84hprop_runDFSTDouble = testDFST dfstDouble double
85 where
86 double :: Seq a -> Seq a
87 double Seq.Empty = Seq.Empty
88 double (a Seq.:<| as) = a Seq.:<| a Seq.:<| double as
89
90unit_runLengthDecode :: Assertion
91unit_runLengthDecode = runDFST dfst input @?= Just (Seq.fromList "aaacc")
92 where
93 input = Seq.fromList [Left 3, Right 'a', Left 0, Right 'b', Left 2, Right 'c']
94 dfst = dfstRunLengthDecode (Set.fromList "abc") 3
95
96hprop_toFST :: Property
97hprop_toFST = property $ do
98 input <- forAll genWord
99 dfst <- forAllWith (show . pretty . toFST) $ genDFST (Set.fromList $ input ++ [0..20]) (Set.fromList [0..20] :: Set Natural)
100
101 runFST (toFST dfst) (Seq.fromList input) === maybeToList (runDFST dfst $ Seq.fromList input)
diff --git a/edit-lens/test/Control/FSTTest.hs b/edit-lens/test/Control/FSTTest.hs
new file mode 100644
index 0000000..f5e02c2
--- /dev/null
+++ b/edit-lens/test/Control/FSTTest.hs
@@ -0,0 +1,187 @@
1module Control.FSTTest where
2
3import Control.FST
4
5import Data.Set (Set)
6import qualified Data.Set as Set
7
8import Data.Map.Strict (Map)
9import qualified Data.Map.Strict as Map
10
11import Data.Sequence (Seq)
12import qualified Data.Sequence as Seq
13
14import Data.Maybe (fromMaybe)
15import Data.Foldable (Foldable(..))
16
17import Control.Monad (when)
18
19import Data.Void
20
21import Test.Tasty
22import Test.Tasty.Hedgehog
23import Test.Tasty.HUnit hiding (assert)
24
25import Hedgehog
26import qualified Hedgehog.Gen as G
27import qualified Hedgehog.Range as R
28
29import Numeric.Natural
30
31import Text.PrettyPrint.Leijen (Pretty(..))
32
33import Control.DeepSeq (force)
34
35
36fstId :: Ord a => Set a -> FST () a a
37fstId syms = FST
38 { stInitial = Set.singleton ()
39 , stTransition = Map.fromList [(((), Just sym), Set.singleton ((), Just sym)) | sym <- Set.toList syms]
40 , stAccept = Set.singleton ()
41 }
42
43fstDouble :: Ord a => Set a -> FST (Maybe a) a a
44fstDouble syms = FST
45 { stInitial = Set.singleton Nothing
46 , stTransition = Map.fromListWith Set.union . concat $
47 [ [((Nothing, Just sym), Set.singleton (Just sym, Just sym)) | sym <- Set.toList syms]
48 , [((Just sym, Nothing), Set.singleton (Nothing, Just sym)) | sym <- Set.toList syms]
49 ]
50 , stAccept = Set.singleton Nothing
51 }
52
53fstRunLengthDecode :: Ord a
54 => Set a -- ^ Alphabet
55 -> Natural -- ^ Upper limit to run length
56 -> FST (Maybe (Natural, Maybe a)) (Either Natural a) a
57fstRunLengthDecode syms lim = FST
58 { stInitial = Set.singleton Nothing
59 , stTransition = Map.fromListWith Set.union . concat $
60 [ [((Nothing, Just (Left n)), Set.singleton (Just (n, Nothing), Nothing)) | n <- [0..lim]]
61 , [((Just (n, Nothing), Just (Right sym)), Set.singleton (Just (n, Just sym), Nothing)) | n <- [0..lim], sym <- Set.toList syms]
62 , [((Just (n, Just sym), Nothing), Set.singleton (Just (pred n, Just sym), Just sym)) | n <- [1..lim], sym <- Set.toList syms]
63 , [((Just (0, Just sym), Nothing), Set.singleton (Nothing, Nothing)) | sym <- Set.toList syms]
64 ]
65 , stAccept = Set.singleton Nothing
66 }
67
68data StRunLengthEncode a = STREInitial
69 | STRECountUp a Natural
70 | STRESwitch (Maybe a) a
71 | STREFinish
72 deriving (Show, Eq, Ord)
73
74fstRunLengthEncode :: Ord a
75 => Bool -- ^ Generate /all/ run length encodings instead of the best
76 -> Set a -- ^ Alphabet
77 -> Natural -- ^ Upper limit to run length
78 -> FST (StRunLengthEncode a) a (Either Natural a)
79fstRunLengthEncode genAll syms lim = FST
80 { stInitial = Set.singleton STREInitial
81 , stTransition = Map.fromListWith Set.union . concat $
82 [ [((STREInitial, Just sym), Set.singleton (STRECountUp sym 1, Nothing)) | sym <- Set.toList syms]
83 , [((STRECountUp sym n, Just sym), Set.singleton (STRECountUp sym (succ n), Nothing)) | sym <- Set.toList syms, n <- [1..pred lim]]
84 , [((STRECountUp sym n, Just sym'), Set.singleton (STRESwitch (Just sym') sym, Just $ Left n)) | n <- [1..lim], sym <- Set.toList syms, sym' <- Set.toList syms, sym /= sym']
85 , [((STRECountUp sym lim, Just sym), Set.singleton (STRESwitch (Just sym) sym, Just $ Left lim)) | sym <- Set.toList syms]
86 , [((STRECountUp sym n, Nothing), Set.singleton (STRESwitch Nothing sym, Just $ Left n)) | sym <- Set.toList syms, n <- [1..lim]]
87 , [((STRESwitch (Just sym') sym, Nothing), Set.singleton (STRECountUp sym' 1, Just $ Right sym)) | sym <- Set.toList syms, sym' <- Set.toList syms]
88 , [((STRESwitch Nothing sym, Nothing), Set.singleton (STREFinish, Just $ Right sym)) | sym <- Set.toList syms]
89 , [((STRECountUp sym n, Just sym), Set.singleton (STRESwitch (Just sym) sym, Just $ Left n)) | n <- [1..lim], sym <- Set.toList syms, genAll]
90 ]
91 , stAccept = Set.fromList [STREInitial, STREFinish]
92 }
93
94
95genWord :: Gen [Natural]
96genWord = G.list (R.linear 0 1000) . G.integral $ R.linear 0 100
97
98
99runFSTDet :: (Show output, Ord output, Show state, Ord state) => (Set Natural -> FST state Natural output) -> (Seq Natural -> Seq output) -> Property
100runFSTDet mkFst f = property $ do
101 input <- forAll genWord
102 let fst = mkFst $ Set.fromList input
103 annotateShow $ pretty fst
104 [f $ Seq.fromList input] === runFST fst (Seq.fromList input)
105
106
107hprop_runFSTId, hprop_runFSTDouble :: Property
108hprop_runFSTId = runFSTDet fstId id
109hprop_runFSTDouble = runFSTDet fstDouble double
110 where
111 double :: Seq a -> Seq a
112 double Seq.Empty = Seq.Empty
113 double (a Seq.:<| as) = a Seq.:<| a Seq.:<| double as
114
115hprop_runWordFST :: Property
116hprop_runWordFST = property $ do
117 input <- forAll genWord
118 let fst = wordFST $ Seq.fromList input
119 annotateShow $ pretty fst
120 [Seq.fromList input] === runFST fst (Seq.empty :: Seq Void)
121
122unit_runLengthDecode, unit_runLengthEncode :: Assertion
123unit_runLengthDecode = runFST fst input @?= [Seq.fromList "aaacc"]
124 where
125 input = Seq.fromList [Left 3, Right 'a', Left 0, Right 'b', Left 2, Right 'c']
126 fst = fstRunLengthDecode (Set.fromList "abc") 3
127unit_runLengthEncode = runFST fst input @?= [Seq.fromList [Left 3, Right 'a', Left 2, Right 'c']]
128 where
129 input = Seq.fromList "aaacc"
130 fst = fstRunLengthEncode False (Set.fromList "abc") 3
131
132hprop_runLength :: Property
133hprop_runLength = property $ do
134 input <- forAll genWord
135 let maxRun = fromMaybe 1 $ countMaxRun input
136 alphabet = Set.fromList input
137 encode = fstRunLengthEncode False alphabet maxRun
138 decode = fstRunLengthDecode alphabet maxRun
139 annotateShow $ countMaxRun input
140 annotateShow $ pretty encode
141 annotateShow $ pretty decode
142 [encoded] <- return . runFST encode $ Seq.fromList input
143 annotateShow $ toList encoded
144 [Seq.fromList input] === runFST decode encoded
145
146hprop_runLength' :: Property
147hprop_runLength' = property $ do
148 input <- forAll genWord
149
150 let maxRun = fromMaybe 1 $ countMaxRun input
151 alphabet = Set.fromList input
152 encode = fstRunLengthEncode True alphabet maxRun
153 decode = fstRunLengthDecode alphabet maxRun
154 annotateShow $ countMaxRun input
155 annotateShow $ pretty encode
156 annotateShow $ pretty decode
157
158 let encoded = runFST encode $ Seq.fromList input
159 annotateShow encoded
160 when (maxRun > 1) $
161 assert $ encoded `longerThan` 1
162
163 encoded' <- forAll $ G.element encoded
164 [Seq.fromList input] === runFST decode encoded'
165 where
166 longerThan :: [a] -> Natural -> Bool
167 longerThan [] _ = False
168 longerThan _ 0 = True
169 longerThan (_:xs) n = longerThan xs $ pred n
170
171countMaxRun :: (Eq a, Foldable f) => f a -> Maybe Natural
172countMaxRun = goMaxRun Nothing Nothing . toList
173 where
174 goMaxRun :: Eq a
175 => Maybe (a, Natural) -- ^ Maximum
176 -> Maybe (a, Natural) -- ^ Current
177 -> [a]
178 -> Maybe Natural
179 goMaxRun Nothing Nothing [] = Nothing
180 goMaxRun (Just (_, n)) (Just (_, n')) []
181 | n' > n = Just n'
182 | otherwise = Just n
183 goMaxRun Nothing Nothing (a:as) = goMaxRun (Just (a, 1)) (Just (a, 1)) as
184 goMaxRun (Just (a, n)) (Just (a', n')) (x:xs)
185 | x == a' = goMaxRun (Just (a, n)) (Just (a', succ n')) xs
186 | n' > n = goMaxRun (Just (a', n')) (Just (x, 1)) xs
187 | otherwise = goMaxRun (Just (a, n)) (Just (x, 1)) xs
diff --git a/edit-lens/test/Driver.hs b/edit-lens/test/Driver.hs
new file mode 100644
index 0000000..327adf4
--- /dev/null
+++ b/edit-lens/test/Driver.hs
@@ -0,0 +1 @@
{-# OPTIONS_GHC -F -pgmF tasty-discover -optF --tree-display #-}
diff --git a/interactive-edit-lens/ChangeLog.md b/interactive-edit-lens/ChangeLog.md
new file mode 100644
index 0000000..8bae309
--- /dev/null
+++ b/interactive-edit-lens/ChangeLog.md
@@ -0,0 +1,5 @@
1# Revision history for edit-lens
2
3## 0.0.0.0
4
5* First version.
diff --git a/interactive-edit-lens/LICENSE b/interactive-edit-lens/LICENSE
new file mode 100644
index 0000000..4522849
--- /dev/null
+++ b/interactive-edit-lens/LICENSE
@@ -0,0 +1,30 @@
1Copyright (c) 2017, Gregor Kleen
2
3All rights reserved.
4
5Redistribution and use in source and binary forms, with or without
6modification, are permitted provided that the following conditions are met:
7
8 * Redistributions of source code must retain the above copyright
9 notice, this list of conditions and the following disclaimer.
10
11 * Redistributions in binary form must reproduce the above
12 copyright notice, this list of conditions and the following
13 disclaimer in the documentation and/or other materials provided
14 with the distribution.
15
16 * Neither the name of Gregor Kleen nor the names of other
17 contributors may be used to endorse or promote products derived
18 from this software without specific prior written permission.
19
20THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
21"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
22LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
23A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT
24OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
25SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT
26LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
27DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
28THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
29(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
30OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
diff --git a/interactive-edit-lens/Setup.hs b/interactive-edit-lens/Setup.hs
new file mode 100644
index 0000000..9a994af
--- /dev/null
+++ b/interactive-edit-lens/Setup.hs
@@ -0,0 +1,2 @@
1import Distribution.Simple
2main = defaultMain
diff --git a/interactive-edit-lens/package.yaml b/interactive-edit-lens/package.yaml
new file mode 100644
index 0000000..9bc3ead
--- /dev/null
+++ b/interactive-edit-lens/package.yaml
@@ -0,0 +1,53 @@
1name: interactive-edit-lens
2version: 0.0.0.0
3license: BSD3
4license-file: LICENSE
5author: Gregor Kleen <aethoago@141.li>
6build-type: Simple
7extra-source-files:
8 - ChangeLog.md
9git: https://git.yggdrasil.li/gkleen/pub/bachelor-thesis
10
11default-extensions:
12 - RecordWildCards
13 - MultiParamTypeClasses
14 - FlexibleInstances
15 - FlexibleContexts
16 - FunctionalDependencies
17 - TupleSections
18 - TypeApplications
19 - ViewPatterns
20 - PatternSynonyms
21 - TypeFamilies
22 - TypeOperators
23 - MultiWayIf
24
25other-extensions:
26 - TemplateHaskell
27
28dependencies:
29 - base
30 - lens
31 - containers
32 - edit-lens
33 - brick
34 - vty
35 - text
36 - text-zipper
37 - dyre
38 - mtl
39 - transformers
40
41# ghc-options: [ -O2 ]
42
43library:
44 source-dirs: src
45 exposed-modules:
46 - Interact
47 - Interact.Types
48
49executables:
50 interact:
51 ghc-options: [ -threaded ]
52 source-dirs: src
53 main: Main.hs
diff --git a/interactive-edit-lens/src/Interact.hs b/interactive-edit-lens/src/Interact.hs
new file mode 100644
index 0000000..3aab5c2
--- /dev/null
+++ b/interactive-edit-lens/src/Interact.hs
@@ -0,0 +1,271 @@
1{-# LANGUAGE ScopedTypeVariables
2 , OverloadedStrings
3 #-}
4
5module Interact
6 ( interactiveEditLens
7 , module Interact.Types
8 , module Config.Dyre
9 ) where
10
11import Prelude hiding (init)
12
13import Interact.Types
14
15import Data.Text (Text)
16import qualified Data.Text as Text
17
18import Data.Text.Zipper
19
20import Data.Sequence (Seq)
21import qualified Data.Sequence as Seq
22
23import Control.Lens
24import Numeric.Lens
25import System.IO
26import Control.Monad
27import Control.Monad.RWS hiding (Last(..), (<>))
28import Control.Monad.Trans.Maybe
29import Control.Monad.Trans.Reader (runReaderT)
30
31import Data.Bool (bool)
32import Data.Tuple (swap)
33import Data.Maybe (fromMaybe)
34import Data.List (groupBy)
35import Data.Function (on)
36import Data.Char (isSpace)
37
38import Data.Foldable (Foldable(toList))
39
40import Brick hiding (on)
41import Brick.Focus
42import Brick.Widgets.Center
43import Brick.Widgets.Border
44import Graphics.Vty hiding (showCursor)
45
46import Config.Dyre
47
48import System.IO.Unsafe
49import Debug.Trace
50
51interactiveEditLens :: (Params (InteractConfig c) -> Params (InteractConfig c)) -> InteractConfig c -> IO ()
52interactiveEditLens f = wrapMain . f $ defaultParams
53 { projectName = "interact-edit-lens"
54 , showError = \s err -> s & compileError .~ Just err
55 , realMain = interactiveEditLens'
56 }
57
58interactiveEditLens' :: forall c. InteractConfig c -> IO ()
59interactiveEditLens' cfg@InteractConfig{..}
60 | Just err <- icfgCompileError
61 = hPutStrLn stderr err
62 | otherwise
63 = void . defaultMain app $! initialState &?~ do
64 let
65 a :: Lens' (InteractState c) (Last Validity, Last (Seq Char, Int), StringEdits Natural Char)
66 a = case icfgInitial of
67 InitialRight _ -> right
68 _other -> left
69 b :: Lens' (InteractState c) (Last Validity, Last (Seq Char, Int), StringEdits Natural Char)
70 b = case icfgInitial of
71 InitialRight _ -> left
72 _other -> right
73 dir :: InteractDirection
74 dir = case icfgInitial of
75 InitialRight _ -> PropagateLeft
76 _other -> PropagateRight
77 aDom :: Seq Char
78 (view charseq -> aDom) = case icfgInitial of
79 InitialRight t -> t
80 InitialLeft t -> t
81 InitialEmpty -> ""
82 doEdit $ divInit aDom & stringEdits . sePos %~ (fromIntegral :: Natural -> Integer)
83 -- a .= (Last Valid, Last (aDom, 0))
84 -- bEdit <- prop dir $ divInit aDom
85 -- (b %=) . maybe id (<>) <=< runMaybeT $ do
86 -- bDom <- use $ b . _2 . _Wrapped . _1
87 -- bDom' <- MaybeT . return $ bDom `apply` bEdit
88 -- return $ (Last Valid, Last (bDom', 0))
89 where
90 infix 1 &?~
91
92 (&?~) :: a -> RWS (InteractConfig c) () a b -> a
93 st &?~ act = (\(s, ()) -> s) $ execRWS act cfg st
94
95 actOn = (&?~)
96
97 initialState :: InteractState c
98 initialState = InteractState
99 { istComplement = ground icfgLens
100 , istLeft = (Last Valid, Last (init @(StringEdits Natural Char), 0), mempty)
101 , istRight = (Last Valid, Last (init @(StringEdits Natural Char), 0), mempty)
102 , istFocus = focusRing [LeftEditor, RightEditor] &
103 focusSetCurrent (case icfgInitial of InitialRight _ -> RightEditor; _other -> LeftEditor)
104 }
105
106 app :: InteractApp c
107 app = App{..}
108
109 appDraw :: InteractState c -> [Widget InteractName]
110 appDraw InteractState{..} = [ editors ]
111 where
112 editors = hBox
113 [ mbInvalid (withFocusRing istFocus renderEditor') (istLeft `WithName` LeftEditor)
114 , vBorder
115 , mbInvalid (withFocusRing istFocus renderEditor') (istRight `WithName` RightEditor)
116 ]
117 renderEditor' :: Bool -> (Seq Char, Int) `WithName` InteractName -> Widget InteractName
118 renderEditor' foc ((content, cPos) `WithName` n)
119 = txt (review charseq content)
120 & bool id (showCursor n cPos') foc
121 & visibleRegion cPos' (1, 1)
122 & viewport n Both
123 where
124 (cPrefix, _) = Seq.splitAt cPos content
125 newls = Seq.findIndicesR (== '\n') cPrefix
126 cPos' = case newls of
127 (p:_) -> Location (pred $ cPos - p, length newls)
128 [] -> Location (cPos, 0)
129 mbInvalid _ ((Last Invalid, _ , _) `WithName` _)
130 = txt "Invalid"
131 & border
132 & center
133 mbInvalid f ((Last Valid , Last x, _) `WithName` n) = f $ x `WithName` n
134
135 appHandleEvent :: InteractState c -> BrickEvent InteractName InteractEvent -> EventM InteractName (Next (InteractState c))
136 appHandleEvent st@InteractState{..} (VtyEvent ev) = case ev of
137 EvKey KEsc [] -> halt st
138 EvKey (KChar 'c') [MCtrl] -> halt st
139 EvKey (KChar '\t') [] -> continue $ st & focus %~ focusNext
140 EvKey KBackTab [] -> continue $ st & focus %~ focusPrev
141 EvKey (KChar 'a') [MCtrl] -> continue $ st &?~ doMove
142 (moveSplit (== '\n') $ \(c, (l, p)) -> if any (== '\n') (c l) || Seq.null (c l) then (pred l, 0) else (l, 0))
143 EvKey (KChar 'e') [MCtrl] -> continue $ st &?~ doMove
144 (moveSplit (== '\n') $ \(c, (l, p)) -> if any (== '\n') $ c l then (pred l, Seq.length . c $ pred l) else (l, Seq.length $ c l))
145 EvKey KLeft [MCtrl] -> continue $ st &?~ doMove
146 (moveSplit isSpace $ \(c, (l, _)) -> if any isSpace (c l) || Seq.null (c l) then (pred l, 0) else (l - 2, 0))
147 EvKey KRight [MCtrl] -> continue $ st &?~ doMove
148 (moveSplit isSpace $ \(c, (l, _)) -> if any isSpace $ c l then (succ l, 0) else (l + 2, 0))
149 EvKey KUp [MCtrl] -> continue $ st &?~ doMove
150 (moveSplit (== '\n') $ \(c, (l, p)) -> if any (== '\n') (c l) || Seq.null (c l) then (pred l, p) else (l - 2, p))
151 EvKey KDown [MCtrl] -> continue $ st &?~ doMove
152 (moveSplit (== '\n') $ \(c, (l, p)) -> if any (== '\n') (c l) then (succ l, p) else (l + 2, p))
153 EvKey KLeft [] -> continue $ st &?~ doMove moveLeft
154 EvKey KRight [] -> continue $ st &?~ doMove moveRight
155 EvKey KDel [] -> continue $ st &?~ doEdit (delete 0)
156 EvKey KBS [] -> continue . actOn st $ do
157 focused' <- preuse $ focused . _2 . _Wrapped
158 doEdit . delete $ -1
159 unless (maybe False ((==) <$> view _2 <*> view (_1 . to Seq.length)) focused') $
160 doMove moveLeft
161 EvKey (KChar c) [] -> continue . actOn st $ do
162 doEdit $ insert 0 c
163 doMove moveRight
164 EvKey KEnter [] -> continue . actOn st $ do
165 doEdit $ insert 0 '\n'
166 doMove moveRight
167 other -> suspendAndResume $ do
168 traceIO $ "Unhandled event:\n\t" ++ show other
169 return st
170 -- where
171 -- editorMovement f = continue $ st & focused . _Just . editContentsL %~ f
172 appHandleEvent st _ = continue st
173
174 doMove = zoom $ focused . _2 . _Wrapped
175
176 moveLeft, moveRight :: MonadState (Seq Char, Int) m => m ()
177 moveLeft = modify $ \now@(_, nowP) -> if
178 | nowP > 0 -> now & _2 %~ pred
179 | otherwise -> now
180 moveRight = modify $ \now@(contents, nowP) -> if
181 | nowP < length contents -> now & _2 %~ succ
182 | otherwise -> now
183
184 moveSplit :: MonadState (Seq Char, Int) m
185 => (Char -> Bool) -- ^ Separator predicate
186 -> (((Int -> Seq Char), (Int, Int)) -> (Int, Int)) -- ^ Move in split coordinates (e.g. @(line, charInLine)@) with access to the focused fragment
187 -> m ()
188 moveSplit splitPred relMove = modify $ \now@(toList -> contentsStr, nowP)
189 -> let splitContents = groupBy ((==) `on` splitPred) contentsStr
190 traceShow x y = flip seq y . unsafePerformIO . appendFile "interact.log" . (<> "\n\n") $ show x
191 (before, mCurrent, after) = snd . (\x -> traceShow (nowP, x) x) $ foldl go (0, ([], Nothing, [])) splitContents
192 go acc@(i, st) cGroup
193 | i <= nowP, nowP < i + length cGroup = (i + length cGroup, st & _2 .~ Just cGroup)
194 | i + length cGroup <= nowP = (i + length cGroup, st & _1 %~ (flip snoc cGroup))
195 | otherwise = (i + length cGroup, st & _3 %~ (flip snoc cGroup))
196 relPos = (length before, nowP - sum (map length before))
197 (newL, newS) = relMove (\i -> if 0 <= i && i < length splitContents then Seq.fromList $ splitContents !! i else Seq.empty, relPos)
198 newPos
199 | null splitContents
200 , newL /= 0 || newS /= 0 = (0, 0)
201 | newL >= length splitContents = (pred $ length splitContents, length $ last splitContents)
202 | newL < 0 = (0, 0)
203 | newS < 0 = (newL, 0)
204 | newS > length (splitContents !! newL) = (newL, length $ splitContents !! newL)
205 | otherwise = (newL, newS)
206 in now & _2 .~ sum (map length $ take (fst newPos) splitContents) + snd newPos
207
208 appStartEvent :: InteractState c -> EventM InteractName (InteractState c)
209 appStartEvent = return
210
211 appAttrMap :: InteractState c -> AttrMap
212 appAttrMap = const $ attrMap defAttr []
213
214 appChooseCursor :: InteractState c -> [CursorLocation InteractName] -> Maybe (CursorLocation InteractName)
215 appChooseCursor = focusRingCursor istFocus
216
217prop :: forall st cfg m.
218 ( MonadState st m
219 , MonadReader cfg m
220 , HasComplement st (Complement cfg)
221 , HasEditLens cfg (StringEdits Natural Char) (StringEdits Natural Char)
222 )
223 => InteractDirection -> StringEdits Natural Char -> m (StringEdits Natural Char)
224prop dir edits = do
225 propD <- case dir of
226 PropagateRight -> asks propR
227 PropagateLeft -> asks propL
228 (c, res) <- propD . (, edits) <$> use complement
229 unsafePerformIO . fmap return . appendFile "interact.log" . (<> "\n\n") $ show (edits, dir, res)
230 res <$ assign complement c
231
232doEdit :: forall m c.
233 ( MonadState (InteractState c) m
234 , MonadReader (InteractConfig c) m
235 )
236 => StringEdits Integer Char -> m ()
237doEdit relativeEdit = void . runMaybeT $ do
238 currentFocus <- MaybeT $ uses focus focusGetCurrent
239 let direction
240 | RightEditor <- currentFocus = PropagateLeft
241 | otherwise = PropagateRight
242 aL :: Lens' (InteractState c) (Last Validity, Last (Seq Char, Int), StringEdits Natural Char)
243 aL | PropagateRight <- direction = left
244 | PropagateLeft <- direction = right
245 bL :: Lens' (InteractState c) (Last Validity, Last (Seq Char, Int), StringEdits Natural Char)
246 bL | PropagateRight <- direction = right
247 | PropagateLeft <- direction = left
248 (aN, bN) = bool swap id (direction == PropagateRight) (LeftEditor, RightEditor)
249 currentZipper <- use $ aL . _2 . _Wrapped
250 let currentPos = currentZipper ^. _2
251 absoluteEdit <- MaybeT . return $ do
252 let minOffset = minimumOf (stringEdits . sePos) relativeEdit
253 guard $ maybe True (\o -> 0 <= currentPos + fromIntegral o) minOffset
254 return $ relativeEdit & stringEdits . sePos %~ (\n -> fromIntegral $ currentPos + fromIntegral n)
255 newContent <- MaybeT . return $ view _1 currentZipper `apply` absoluteEdit
256 let currentPos'
257 | currentPos < 0 = 0
258 | currentPos > length newContent = length newContent
259 | otherwise = currentPos
260 aL . _2 %= (<> Last (newContent, currentPos'))
261 absoluteEdit' <- uses (aL . _3) (absoluteEdit `mappend`)
262 bEdits <- prop direction absoluteEdit'
263 bDom <- use $ bL . _2 . _Wrapped . _1
264 case bDom `apply` bEdits of
265 Nothing -> do
266 bL . _1 %= (<> Last Invalid)
267 aL . _3 .= absoluteEdit'
268 Just bDom' -> do
269 bL . _1 %= (<> Last Valid)
270 bL . _2 . _Wrapped . _1 .= bDom'
271 aL . _3 .= mempty
diff --git a/interactive-edit-lens/src/Interact/Types.hs b/interactive-edit-lens/src/Interact/Types.hs
new file mode 100644
index 0000000..a4d08ac
--- /dev/null
+++ b/interactive-edit-lens/src/Interact/Types.hs
@@ -0,0 +1,120 @@
1{-# LANGUAGE TemplateHaskell #-}
2{-# OPTIONS_GHC -fno-warn-orphans #-}
3
4module Interact.Types
5 ( InteractName(..)
6 , _LeftEditor, _RightEditor, _PrimitiveName
7 , Validity, pattern Valid, pattern Invalid
8 , InteractState(..)
9 , HasLeft(..), HasRight(..), HasComplement(..), HasFocus(..), HasFocused(..)
10 , InteractInitial(..)
11 , _InitialLeft, _InitialRight, _InitialEmpty
12 , InteractConfig(..)
13 , HasInitial(..), HasLens(..), HasCompileError(..)
14 , InteractEvent
15 , InteractApp
16 , InteractDirection(..)
17 , charseq
18 , WithName(..)
19 , module Control.Edit
20 , module Control.Lens.Edit
21 , module Control.DFST.Lens
22 , module Data.Semigroup
23 , module Numeric.Natural
24 ) where
25
26import Data.Text (Text)
27import qualified Data.Text as Text
28import Data.Text.Lens
29
30import Data.Sequence (Seq(..))
31import qualified Data.Sequence as Seq
32
33import qualified Data.Foldable as Foldable
34
35import Data.Semigroup (Semigroup(..), Last(..))
36import Numeric.Natural
37
38import Brick
39import Brick.Focus
40import Brick.Widgets.Edit
41
42import Control.Lens
43import Control.Lens.TH
44import Control.Edit
45import Control.Lens.Edit
46import Control.DFST.Lens
47
48import Data.Text.Zipper.Generic
49
50
51data InteractName
52 = LeftEditor
53 | RightEditor
54 | PrimitiveName !Text
55 deriving (Eq, Ord, Show, Read)
56
57makePrisms ''InteractName
58
59type Validity = Bool
60pattern Valid = True
61pattern Invalid = False
62
63data InteractState c = InteractState
64 { istLeft, istRight :: (Last Validity, Last (Seq Char, Int), StringEdits Natural Char)
65 , istComplement :: c
66 , istFocus :: FocusRing InteractName
67 }
68
69makeLensesWith abbreviatedFields ''InteractState
70
71class HasFocused s a | s -> a where
72 focused :: Traversal' s a
73
74instance HasFocused (InteractState c) (Last Validity, Last (Seq Char, Int), StringEdits Natural Char) where
75 focused f st@InteractState{..} = case focusGetCurrent istFocus of
76 Just LeftEditor -> left f st
77 Just RightEditor -> right f st
78 _other -> pure st
79
80data InteractInitial
81 = InitialLeft Text
82 | InitialRight Text
83 | InitialEmpty
84 deriving (Eq, Ord, Show, Read)
85
86makePrisms ''InteractInitial
87
88data InteractConfig c = InteractConfig
89 { icfgInitial :: InteractInitial
90 , icfgLens :: EditLens c (StringEdits Natural Char) (StringEdits Natural Char)
91 , icfgCompileError :: Maybe String
92 }
93
94instance HasEditLens (InteractConfig c) (StringEdits Natural Char) (StringEdits Natural Char) where
95 type Complement (InteractConfig c) = c
96 ground = ground . icfgLens
97 propR = propR . icfgLens
98 propL = propL . icfgLens
99
100makeLensesWith abbreviatedFields ''InteractConfig
101
102charseq :: Iso' Text (Seq Char)
103charseq = iso Text.unpack Text.pack . iso Seq.fromList Foldable.toList
104
105type InteractEvent = ()
106
107type InteractApp c = App (InteractState c) InteractEvent InteractName
108
109data InteractDirection = PropagateLeft | PropagateRight
110 deriving (Eq, Ord, Enum, Bounded, Show, Read)
111
112makePrisms ''InteractDirection
113
114
115infixr 1 `WithName`
116data WithName x n = WithName x n
117 deriving (Eq, Ord, Show, Read)
118
119instance Named (x `WithName` n) n where
120 getName (_ `WithName` n) = n
diff --git a/interactive-edit-lens/src/Main.hs b/interactive-edit-lens/src/Main.hs
new file mode 100644
index 0000000..f7bc806
--- /dev/null
+++ b/interactive-edit-lens/src/Main.hs
@@ -0,0 +1,94 @@
1{-# LANGUAGE OverloadedStrings
2 , ExistentialQuantification
3 #-}
4
5module Main where
6
7import Interact
8import Control.DFST.Lens
9import Control.DFST
10
11import Data.Map (Map)
12import qualified Data.Map as Map
13
14import Data.Set (Set)
15import qualified Data.Set as Set
16
17import Data.Sequence (Seq)
18import qualified Data.Sequence as Seq
19
20import Data.Char
21
22import System.Environment
23import System.Exit
24
25import Debug.Trace
26
27data SomeDFST = forall state. (Ord state, Show state) => SomeDFST { someDFST :: DFST state Char Char }
28
29data JsonNewlState = JNUndeterminedStructure | JNOutsideStructure | JNInsideStructure | JNInsideString | JNEscape
30 deriving (Eq, Ord, Show, Read)
31
32dfstMap :: String -> Maybe SomeDFST
33dfstMap "double" = Just . SomeDFST $ DFST
34 { stInitial = ()
35 , stTransition = mconcat
36 [ Map.fromList
37 [(((), sym), ((), Seq.fromList [sym, sym])) | sym <- ['a'..'z'] ++ ['A'..'Z'] ++ ['!', ' ']] -- sym <- [minBound..maxBound], isPrint sym]
38 , Map.singleton ((), '\n') ((), Seq.singleton '\n')
39 ]
40 , stAccept = Set.singleton ()
41 }
42dfstMap "id" = Just . SomeDFST $ DFST
43 { stInitial = ()
44 , stTransition = Map.fromList
45 [(((), sym), ((), Seq.singleton sym)) | sym <- ['a'..'z'] ++ ['A'..'Z'] ++ ['!', ' ']] -- sym <- [minBound..maxBound], isPrint sym]
46 , stAccept = Set.singleton ()
47 }
48dfstMap "alternate" = Just . SomeDFST $ DFST
49 { stInitial = 0 :: Int
50 , stTransition = mconcat
51 [ Map.fromList [((0, sym), (1, Seq.singleton sym)) | sym <- ['a'..'z'] ++ ['A'..'Z'] ++ ['!', ' ']] -- sym <- [minBound..maxBound], isPrint sym]
52 , Map.fromList [((1, sym), (0, Seq.fromList [toUpper sym, toUpper sym])) | sym <- ['a'..'z'] ++ ['A'..'Z'] ++ ['!', ' ']] -- sym <- [minBound..maxBound], isPrint sym]
53 ]
54 , stAccept = Set.fromList [0]
55 }
56dfstMap "json-newl" = Just . SomeDFST $ DFST
57 { stInitial = JNOutsideStructure
58 , stTransition = mconcat
59 [ Map.fromList [((jnOutside, sym), (jnOutside, Seq.empty)) | sym <- whitespace, jnOutside <- [JNOutsideStructure, JNUndeterminedStructure]]
60 , Map.fromList [((jnOutside, sym), (JNInsideStructure, Seq.fromList [sym, ' '])) | sym <- "[{", jnOutside <- [JNOutsideStructure, JNInsideStructure, JNUndeterminedStructure]]
61 , Map.fromList [((JNInsideStructure, sym), (JNInsideStructure, Seq.empty)) | sym <- whitespace]
62 , Map.fromList [((jnInside, sym), (JNUndeterminedStructure, Seq.fromList ['\n', sym])) | sym <- "]}", jnInside <- [JNInsideStructure, JNUndeterminedStructure]]
63 , Map.fromList [((jnInside, ','), (JNInsideStructure, Seq.fromList "\n, ")) | jnInside <- [JNInsideStructure, JNUndeterminedStructure] ]
64 , Map.fromList [((jnInside, ':'), (JNInsideStructure, Seq.fromList " : ")) | jnInside <- [JNInsideStructure, JNUndeterminedStructure] ]
65 , Map.fromList [((jn, '"'), (JNInsideString, Seq.singleton '"')) | jn <- [JNUndeterminedStructure, JNInsideStructure]]
66 , Map.fromList [((JNInsideString, sym), (JNInsideString, Seq.singleton sym)) | sym <- ['a'..'z'] ++ ['A'..'Z'] ++ ",.!?: "]
67 , Map.singleton (JNInsideString, '"') (JNUndeterminedStructure, Seq.singleton '"')
68 , Map.singleton (JNInsideString, '\\') (JNEscape, Seq.singleton '\\')
69 , Map.singleton (JNEscape, '"') (JNInsideString, Seq.singleton '"')
70 ]
71 , stAccept = Set.fromList [JNOutsideStructure, JNUndeterminedStructure]
72 }
73 where
74 whitespace = toEnum <$> [0x0020, 0x0009, 0x000a, 0x000d]
75dfstMap _ = Nothing
76
77main :: IO ()
78main = do
79 args <- getArgs
80
81 dfst <- case args of
82 [name] | Just dfst <- dfstMap name
83 -> return dfst
84 _ -> exitWith $ ExitFailure 2
85
86 interactiveEditLens' dfst
87
88interactiveEditLens' :: SomeDFST -> IO ()
89interactiveEditLens' (SomeDFST dfst)
90 = interactiveEditLens id $ InteractConfig
91 { icfgInitial = InitialEmpty
92 , icfgLens = dfstLens dfst
93 , icfgCompileError = Nothing
94 }
diff --git a/literature.meta.yml b/literature.meta.yml
new file mode 100644
index 0000000..9eb6cc7
--- /dev/null
+++ b/literature.meta.yml
@@ -0,0 +1,5 @@
1---
2lang: de-de
3link-citations: true
4bibliography: literature.bibtex
5...
diff --git a/stack.nix b/stack.nix
index eec431d..dba6b1d 100644
--- a/stack.nix
+++ b/stack.nix
@@ -1,4 +1,4 @@
1{ ghc, nixpkgs ? (import <nixpkgs> {}) }: 1{ ghc, nixpkgs ? (import <nixos> {}) }:
2 2
3let 3let
4 inherit (nixpkgs) haskell pkgs; 4 inherit (nixpkgs) haskell pkgs;
diff --git a/stack.yaml b/stack.yaml
index f36abc3..92dd54f 100644
--- a/stack.yaml
+++ b/stack.yaml
@@ -5,7 +5,11 @@ packages:
5 git: https://github.com/pngwjpgh/composition-tree 5 git: https://github.com/pngwjpgh/composition-tree
6 commit: c9c1c11f6820bbbe1ac96513a66609599483bdb6 6 commit: c9c1c11f6820bbbe1ac96513a66609599483bdb6
7 extra-dep: true 7 extra-dep: true
8 - interactive-edit-lens
8nix: 9nix:
9 packages: [] 10 packages: []
10 pure: false 11 pure: false
11 shell-file: ./stack.nix 12 shell-file: ./stack.nix
13build:
14 library-profiling: true
15 executable-profiling: true
diff --git a/thesis.pdf.gup b/thesis.pdf.gup
index 2167f7b..6e2fa65 100755
--- a/thesis.pdf.gup
+++ b/thesis.pdf.gup
@@ -1,10 +1,13 @@
1#!/usr/bin/env zsh 1#!/usr/bin/env zsh
2 2
3gup -u edit-lens/src/Control/Edit.lhs
3gup -u edit-lens/src/Control/Lens/Edit.lhs 4gup -u edit-lens/src/Control/Lens/Edit.lhs
4gup -u edit-lens/src/Control/Lens/Edit/Compose.lhs 5gup -u edit-lens/src/Control/FST.lhs
6gup -u edit-lens/src/Control/DFST.lhs
7gup -u edit-lens/src/Control/DFST/Lens.lhs
5 8
6bDir=$(pwd) 9bDir=$(pwd)
7 10
8cd .. 11cd ..
9 12
10exec gup/pdf.gup $1 ${bDir}/$2 \ No newline at end of file 13exec gup/pdf.gup $1 ${bDir}/$2
diff --git a/thesis.tex b/thesis.tex
index 6b94318..cf5c489 100644
--- a/thesis.tex
+++ b/thesis.tex
@@ -1,5 +1,19 @@
1\section{Edit-lenses}
2
1Ziel ist es zunächst edit-lenses alá \cite{hofmann2012edit} in Haskell zur Verfügung zu stellen. 3Ziel ist es zunächst edit-lenses alá \cite{hofmann2012edit} in Haskell zur Verfügung zu stellen.
2Dabei werden wir die Definitionen aus \cite{hofmann2012edit} sowohl in natürlicher Sprache als auch in lauffähigem Haskell vorstellen: 4Dabei werden wir die Definitionen aus \cite{hofmann2012edit} sowohl in natürlicher Sprache als auch in lauffähigem Haskell vorstellen:
3 5
4\input{./edit-lens/src/Control/Edit.lhs} 6\input{./edit-lens/src/Control/Edit.lhs}
5\input{./edit-lens/src/Control/Lens/Edit.lhs} 7\input{./edit-lens/src/Control/Lens/Edit.lhs}
8
9\section{Finite state transducers}
10
11\input{./edit-lens/src/Control/FST.lhs}
12\input{./edit-lens/src/Control/DFST.lhs}
13
14\subsection{Edit-lenses für deterministic finite state transducers}
15\input{./edit-lens/src/Control/DFST/Lens.lhs}
16
17% \section{Container}
18
19% TODO: recover from git