diff options
author | Gregor Kleen <gkleen@yggdrasil.li> | 2019-05-30 12:18:08 +0200 |
---|---|---|
committer | Gregor Kleen <gkleen@yggdrasil.li> | 2019-05-30 12:18:08 +0200 |
commit | f4c419b9ddec15bad267a4463f0720d6e28042d2 (patch) | |
tree | 54a0259116476150247619c4410eae33f8669314 /edit-lens/src/Control/Lens | |
parent | 8afbe1f7df24034dd16fdf2e89b0665b2318ae2a (diff) | |
download | incremental-dfsts-f4c419b9ddec15bad267a4463f0720d6e28042d2.tar incremental-dfsts-f4c419b9ddec15bad267a4463f0720d6e28042d2.tar.gz incremental-dfsts-f4c419b9ddec15bad267a4463f0720d6e28042d2.tar.bz2 incremental-dfsts-f4c419b9ddec15bad267a4463f0720d6e28042d2.tar.xz incremental-dfsts-f4c419b9ddec15bad267a4463f0720d6e28042d2.zip |
Further work
Diffstat (limited to 'edit-lens/src/Control/Lens')
-rw-r--r-- | edit-lens/src/Control/Lens/Edit.lhs | 6 | ||||
l--------- | edit-lens/src/Control/Lens/Edit.lhs.tex | 1 | ||||
-rw-r--r-- | edit-lens/src/Control/Lens/Edit/ActionTree.lhs | 204 | ||||
l--------- | edit-lens/src/Control/Lens/Edit/ActionTree.lhs.tex | 1 |
4 files changed, 209 insertions, 3 deletions
diff --git a/edit-lens/src/Control/Lens/Edit.lhs b/edit-lens/src/Control/Lens/Edit.lhs index 96b2114..6561528 100644 --- a/edit-lens/src/Control/Lens/Edit.lhs +++ b/edit-lens/src/Control/Lens/Edit.lhs | |||
@@ -12,7 +12,7 @@ import Control.Edit | |||
12 | \end{comment} | 12 | \end{comment} |
13 | 13 | ||
14 | \begin{defn}[Zustandsbehaftete Monoidhomomorphismen] | 14 | \begin{defn}[Zustandsbehaftete Monoidhomomorphismen] |
15 | Gegeben 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: | 15 | Gegeben eine Menge $C$ von \emph{Komplementen} und zwei 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: |
16 | 16 | ||
17 | \begin{itemize} | 17 | \begin{itemize} |
18 | \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)$ |
@@ -28,7 +28,7 @@ type StateMonoidHom s m n = (s, m) -> (s, n) | |||
28 | \end{defn} | 28 | \end{defn} |
29 | 29 | ||
30 | \begin{defn}[edit-lenses] | 30 | \begin{defn}[edit-lenses] |
31 | Fü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: | 31 | Fü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 \in C$ und einer \emph{Konsistenzrelation} $K \subset \Dom M \times C \times \Dom N$ sodass gilt: |
32 | 32 | ||
33 | \begin{itemize} | 33 | \begin{itemize} |
34 | \item $(\init_M, \ground_C, \init_N) \in K$ | 34 | \item $(\init_M, \ground_C, \init_N) \in K$ |
@@ -67,7 +67,7 @@ instance (Module m, Module n) => HasEditLens (EditLens c m n) m n where | |||
67 | \end{code} | 67 | \end{code} |
68 | \end{defn} | 68 | \end{defn} |
69 | 69 | ||
70 | \paragraph{Kompatibilität mit bestehenden lens frameworks} | 70 | \subsection{Kompatibilität mit bestehenden lens frameworks} |
71 | 71 | ||
72 | Das einschlägige bestehende lens framework \cite{lens} konstruiert seine Linsen alá \citeauthor{laarhoven} wie folgt: | 72 | Das einschlägige bestehende lens framework \cite{lens} konstruiert seine Linsen alá \citeauthor{laarhoven} wie folgt: |
73 | 73 | ||
diff --git a/edit-lens/src/Control/Lens/Edit.lhs.tex b/edit-lens/src/Control/Lens/Edit.lhs.tex new file mode 120000 index 0000000..33d3341 --- /dev/null +++ b/edit-lens/src/Control/Lens/Edit.lhs.tex | |||
@@ -0,0 +1 @@ | |||
Edit.lhs \ No newline at end of file | |||
diff --git a/edit-lens/src/Control/Lens/Edit/ActionTree.lhs b/edit-lens/src/Control/Lens/Edit/ActionTree.lhs new file mode 100644 index 0000000..6632dce --- /dev/null +++ b/edit-lens/src/Control/Lens/Edit/ActionTree.lhs | |||
@@ -0,0 +1,204 @@ | |||
1 | \begin{comment} | ||
2 | \begin{code} | ||
3 | {-# LANGUAGE ScopedTypeVariables | ||
4 | , TypeApplications | ||
5 | , TypeFamilyDependencies | ||
6 | #-} | ||
7 | |||
8 | module Control.Lens.Edit.ActionTree | ||
9 | ( Action(..) | ||
10 | , treeLens | ||
11 | ) where | ||
12 | |||
13 | import Control.Edit | ||
14 | import Control.Edit.String | ||
15 | import Control.Edit.String.Affected | ||
16 | import Control.Lens.Edit | ||
17 | |||
18 | import Control.Lens | ||
19 | |||
20 | import Numeric.Natural | ||
21 | import Numeric.Interval (Interval, (...)) | ||
22 | import qualified Numeric.Interval as Int | ||
23 | |||
24 | import Data.Compositions (Compositions) | ||
25 | import qualified Data.Compositions as Comp | ||
26 | |||
27 | import Data.Algorithm.Diff (Diff, getDiff) | ||
28 | import qualified Data.Algorithm.Diff as Diff | ||
29 | |||
30 | import Data.Sequence (Seq((:<|), (:|>))) | ||
31 | import qualified Data.Sequence as Seq | ||
32 | import Data.Set (Set) | ||
33 | import qualified Data.Set as Set | ||
34 | |||
35 | import Data.Monoid | ||
36 | import Data.Function (on) | ||
37 | import Data.Foldable (toList) | ||
38 | import Data.Maybe (fromMaybe) | ||
39 | |||
40 | import System.IO (Handle, hPutStrLn, IOMode(AppendMode), withFile) | ||
41 | import System.IO.Unsafe | ||
42 | \end{code} | ||
43 | \end{comment} | ||
44 | |||
45 | Das beschrieben Verfahren wurde prinzipiell agnostisch in Bezug auf die konkret gewählte Parser-Konstruktion gewählt. | ||
46 | |||
47 | Hierfür wurden die benötigten Operationen auf der DFST-Wirkung und das in $\Lleftarrow$ verwendete Suchschema abstrakt als Typklasse angegeben: | ||
48 | |||
49 | \begin{code} | ||
50 | class Monoid action => Action action input output | action -> input, action -> output where | ||
51 | \end{code} | ||
52 | \begin{comment} | ||
53 | \begin{code} | ||
54 | -- | Most operations of `Action` permit access to some underlying description of the parser (i.e. an automaton) | ||
55 | type ActionParam action = param | param -> action | ||
56 | |||
57 | -- | A full capture of the Parser-State (i.e. a state for a given automaton) | ||
58 | type ActionState action :: * | ||
59 | |||
60 | -- | `mempty` should be neutral under `(<>)`, `actionFail` should be absorptive | ||
61 | actionFail :: action | ||
62 | |||
63 | -- | Construct an @action@ from a single character of input | ||
64 | actionSingleInput :: ActionParam action -> input -> action | ||
65 | -- | Initial state of the parser | ||
66 | actionGroundState :: ActionParam action -> ActionState action | ||
67 | -- | Is a certain state acceptable as final? | ||
68 | actionStateFinal :: ActionParam action -> ActionState action -> Bool | ||
69 | -- | Run an @action@ (actually a binary tree thereof, use `Comp.composed` to extract the root) on a given state | ||
70 | actionState :: ActionParam action -> Compositions action -> ActionState action -> Maybe (ActionState action) | ||
71 | -- | What @output@ does running an @action@ on a given state produce? | ||
72 | actionProduces :: ActionParam action -> Compositions action -> ActionState action -> Seq output | ||
73 | -- | What @input@ does running an @action@ on a given state consume? | ||
74 | actionConsumes :: ActionParam action -> Compositions action -> Seq input | ||
75 | |||
76 | -- | Find a new string of @input@-symbols to travel between the given states while producing exactly the given @output@ | ||
77 | -- | ||
78 | -- @actionFindPath@ also has access to the remaining action to be run after it's new @input@ has been consumed. | ||
79 | -- This is necessary to further restrict the considered paths in such a way that the resulting run as a whole is acceptable in the sense of `actionStateFinal`. | ||
80 | actionFindPath :: ActionParam action | ||
81 | -> ActionState action -- ^ From | ||
82 | -> Seq output -- ^ New output to be produced | ||
83 | -> ActionState action -- ^ To | ||
84 | -> Compositions action -- ^ Suffix | ||
85 | -> Maybe (Seq input) | ||
86 | \end{code} | ||
87 | \end{comment} | ||
88 | |||
89 | Das Verfahren kann nun auf andere Sorten von Parser angewendet werden, indem nur die oben aufgeführte \texttt{Action}-Typklasse implementiert wird: | ||
90 | |||
91 | \begin{code} | ||
92 | treeLens :: forall action input output. | ||
93 | ( Ord input, Ord output | ||
94 | , Show input, Show output | ||
95 | , Action action input output | ||
96 | , Show (ActionState action) | ||
97 | ) => ActionParam action -> EditLens (Compositions action) (StringEdits Natural input) (StringEdits Natural output) | ||
98 | \end{code} | ||
99 | \begin{comment} | ||
100 | \begin{code} | ||
101 | treeLens param = EditLens ground propR propL | ||
102 | where | ||
103 | ground :: Compositions action | ||
104 | ground = mempty | ||
105 | |||
106 | propR :: (Compositions action, StringEdits Natural input) | ||
107 | -> (Compositions action, StringEdits Natural output) | ||
108 | propR (c, SEFail) = (c, SEFail) | ||
109 | propR (c, StringEdits Seq.Empty) = (c, mempty) | ||
110 | propR (c, lEs@(StringEdits (es :> e))) | ||
111 | | Just final <- actionState param c' $ actionGroundState @action param | ||
112 | , actionStateFinal param final | ||
113 | = (c', rEs) | ||
114 | | otherwise | ||
115 | = (c, SEFail) | ||
116 | where | ||
117 | Just int = affected lEs | ||
118 | (cAffSuffix, cAffPrefix) = Comp.splitAt (Comp.length c - fromIntegral (Int.inf int)) c | ||
119 | (cSuffix, cPrefix) = Comp.splitAt (Comp.length c - (e ^. sePos . from enum)) c | ||
120 | cSuffix' | ||
121 | | Delete _ <- e | ||
122 | , Comp.length cSuffix > 0 = Comp.take (pred $ Comp.length cSuffix) cSuffix | ||
123 | | Insert _ nChar <- e = cSuffix <> Comp.singleton (actionSingleInput param nChar) | ||
124 | | otherwise = Comp.singleton actionFail | ||
125 | (c', _) = propR (cSuffix' <> cPrefix, StringEdits es) | ||
126 | (cAffSuffix', _) = Comp.splitAt (Comp.length c' - Comp.length cAffPrefix) c' | ||
127 | Just pFinal = actionState param cAffPrefix $ actionGroundState @action param | ||
128 | rEs = strDiff (actionProduces param cAffSuffix pFinal) (actionProduces param cAffSuffix' pFinal) & stringEdits . sePos . from enum +~ length (actionProduces param cAffPrefix $ actionGroundState @action param) | ||
129 | |||
130 | propL :: (Compositions action, StringEdits Natural output) | ||
131 | -> (Compositions action, StringEdits Natural input) | ||
132 | propL (c, StringEdits Seq.Empty) = (c, mempty) | ||
133 | propL (c, es) = fromMaybe (c, SEFail) $ do | ||
134 | -- Determine states @(iState, fState)@ at the boundary of the region affected by @es@ | ||
135 | ((,) <$> Int.inf <*> Int.sup -> (minAff, maxAff)) <- affected es | ||
136 | trace (show (minAff, maxAff)) $ Just () | ||
137 | let | ||
138 | prevTrans :: Natural -> Maybe ( Compositions action {- Run after chosen transition to accepting state -} | ||
139 | , (ActionState action, input, Seq output, ActionState action) | ||
140 | , Compositions action {- Run from `stInitial` up to chosen transition -} | ||
141 | ) | ||
142 | -- ^ Given an index in the output, find the associated transition in @c@ | ||
143 | prevTrans needle = do | ||
144 | let (after, before) = prevTrans' (c, mempty) | ||
145 | transSt <- actionState param before $ actionGroundState @action param | ||
146 | trace ("transSt = " ++ show transSt) $ Just () | ||
147 | let (after', trans) = Comp.splitAt (pred $ Comp.length after) after | ||
148 | [inS] <- return . toList $ actionConsumes param trans | ||
149 | Just postTransSt <- return $ actionState param trans transSt | ||
150 | outSs <- return $ actionProduces param trans transSt | ||
151 | return (after', (transSt, inS, outSs, postTransSt), before) | ||
152 | where | ||
153 | -- | Move monoid summands from @after@ to @before@ until first transition of @after@ produces @needle@ or @after@ is a singleton | ||
154 | prevTrans' :: (Compositions action, Compositions action) | ||
155 | -> (Compositions action, Compositions action) | ||
156 | prevTrans' (after, before) | ||
157 | | producedNext > needle = (after, before) | ||
158 | | Comp.length after == 1 = (after, before) | ||
159 | | otherwise = prevTrans' (after', before') | ||
160 | where | ||
161 | producedNext = fromIntegral . Seq.length . traceShowId . actionProduces param before' $ actionGroundState @action param | ||
162 | (after', nextTrans) = Comp.splitAt (pred $ Comp.length after) after | ||
163 | before' = nextTrans `mappend` before | ||
164 | (_, (iState, _, _, _), prefix) <- prevTrans minAff | ||
165 | trace (show (iState, Comp.length prefix)) $ Just () | ||
166 | (suffix, (pfState, _, _, fState), _) <- prevTrans maxAff | ||
167 | trace (show (pfState, fState, Comp.length suffix)) $ Just () | ||
168 | |||
169 | newOut <- actionProduces param c (actionGroundState @action param) `apply` es | ||
170 | let affNewOut = (\s -> Seq.take (Seq.length s - Seq.length (actionProduces param suffix fState)) s) $ Seq.drop (Seq.length . actionProduces param prefix $ actionGroundState @action param) newOut | ||
171 | trace (show (iState, fState, affNewOut)) $ Just () | ||
172 | |||
173 | newIn <- actionFindPath param iState affNewOut fState suffix | ||
174 | |||
175 | let oldIn = actionConsumes param . Comp.drop (Comp.length suffix) $ Comp.take (Comp.length c - Comp.length prefix) c | ||
176 | inDiff = oldIn `strDiff` newIn | ||
177 | diffOffset = fromIntegral . Seq.length $ actionConsumes param prefix | ||
178 | inDiff' = inDiff & stringEdits . sePos +~ diffOffset | ||
179 | |||
180 | trace (show (oldIn, newIn, inDiff')) $ Just () | ||
181 | |||
182 | let affComp = Comp.fromList $ actionSingleInput param <$> toList newIn | ||
183 | |||
184 | return (suffix <> affComp <> prefix, inDiff') | ||
185 | |||
186 | |||
187 | strDiff :: forall sym pos. (Eq sym, Integral pos) => Seq sym -> Seq sym -> StringEdits pos sym | ||
188 | -- ^ @strDiff a b@ calculates a set of edits, which, when applied to @a@, produce @b@ | ||
189 | strDiff a b = snd . foldl toEdit (0, mempty) $ (getDiff `on` toList) a b | ||
190 | where | ||
191 | toEdit :: (pos, StringEdits pos sym) -> Diff sym -> (pos, StringEdits pos sym) | ||
192 | toEdit (n, es) (Diff.Both _ _) = (succ n, es) | ||
193 | toEdit (n, es) (Diff.First _ ) = (n, delete n <> es) | ||
194 | toEdit (n, es) (Diff.Second c) = (succ n, insert n c <> es) | ||
195 | |||
196 | trace :: String -> a -> a | ||
197 | {-# NOINLINE trace #-} | ||
198 | trace str y = flip seq y . unsafePerformIO . withFile "lens.log" AppendMode $ \h -> | ||
199 | hPutStrLn h str | ||
200 | |||
201 | traceShowId :: Show a => a -> a | ||
202 | traceShowId x = trace (show x) x | ||
203 | \end{code} | ||
204 | \end{comment} | ||
diff --git a/edit-lens/src/Control/Lens/Edit/ActionTree.lhs.tex b/edit-lens/src/Control/Lens/Edit/ActionTree.lhs.tex new file mode 120000 index 0000000..6e3c68c --- /dev/null +++ b/edit-lens/src/Control/Lens/Edit/ActionTree.lhs.tex | |||
@@ -0,0 +1 @@ | |||
ActionTree.lhs \ No newline at end of file | |||