summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--edit-lens/src/Control/DFST/Lens.lhs53
1 files changed, 36 insertions, 17 deletions
diff --git a/edit-lens/src/Control/DFST/Lens.lhs b/edit-lens/src/Control/DFST/Lens.lhs
index 35a7d38..3959b39 100644
--- a/edit-lens/src/Control/DFST/Lens.lhs
+++ b/edit-lens/src/Control/DFST/Lens.lhs
@@ -43,7 +43,7 @@ import qualified Data.Algorithm.Diff as Diff
43 43
44import Data.Monoid 44import Data.Monoid
45import Data.Bool (bool) 45import Data.Bool (bool)
46import Data.Maybe (fromMaybe, maybeToList, listToMaybe) 46import Data.Maybe (fromMaybe, maybeToList, listToMaybe, catMaybes)
47import Data.Function (on) 47import Data.Function (on)
48import Data.Foldable (toList) 48import Data.Foldable (toList)
49import Data.List (partition) 49import Data.List (partition)
@@ -178,17 +178,26 @@ Nun gilt es nur noch die Differenz (als `StringEdits`) des vorherigen Suffixes i
178 178
179\begin{code} 179\begin{code}
180 180
181data DFSTAction state input output = DFSTAction { runDFSTAction :: state -> (state, Seq output) } 181data DFSTAction state input output = DFSTAction
182 { runDFSTAction :: state -> (state, Seq output)
183 , dfstaConsumes :: Seq input
184 }
182 185
183instance Monoid (DFSTAction state input output) where 186instance Monoid (DFSTAction state input output) where
184 mempty = DFSTAction $ \x -> (x, Seq.empty) 187 mempty = DFSTAction (\x -> (x, Seq.empty)) Seq.empty
185 DFSTAction f `mappend` DFSTAction g = DFSTAction $ \s -> let ((f -> (s', out')), out) = g s in (s', out <> out') 188 DFSTAction f cf `mappend` DFSTAction g cg = DFSTAction
189 { runDFSTAction = \s -> let ((f -> (s', out')), out) = g s in (s', out <> out')
190 , dfstaConsumes = cg <> cf
191 }
186 192
187type DFSTComplement state input output = Compositions (DFSTAction state input output) 193type DFSTComplement state input output = Compositions (DFSTAction state input output)
188 194
189runDFSTAction' :: DFSTComplement state input output -> state -> (state, Seq output) 195runDFSTAction' :: DFSTComplement state input output -> state -> (state, Seq output)
190runDFSTAction' = runDFSTAction . Comp.composed 196runDFSTAction' = runDFSTAction . Comp.composed
191 197
198dfstaConsumes' :: DFSTComplement state input output -> Seq input
199dfstaConsumes' = dfstaConsumes . Comp.composed
200
192type Debug state input output = (Show state, Show input, Show output) 201type Debug state input output = (Show state, Show input, Show output)
193 202
194type LState state input output = (Natural, (state, Maybe (input, Natural))) 203type LState state input output = (Natural, (state, Maybe (input, Natural)))
@@ -209,7 +218,7 @@ dfstLens dfst@DFST{..} = EditLens ground propR propL
209 (cSuffix, cPrefix) = Comp.splitAt (Comp.length c - (e ^. sePos . from enum)) c 218 (cSuffix, cPrefix) = Comp.splitAt (Comp.length c - (e ^. sePos . from enum)) c
210 cSuffix' 219 cSuffix'
211 | Delete _ <- e = Comp.take (pred $ Comp.length cSuffix) cSuffix -- TODO unsafe 220 | Delete _ <- e = Comp.take (pred $ Comp.length cSuffix) cSuffix -- TODO unsafe
212 | Insert _ nChar <- e = cSuffix <> Comp.singleton (DFSTAction $ \x -> runDFST' dfst x (pure nChar) Seq.empty) 221 | Insert _ nChar <- e = cSuffix <> Comp.singleton (DFSTAction (\x -> runDFST' dfst x (pure nChar) Seq.empty) (Seq.singleton nChar))
213 (pState, pOutput) = runDFSTAction' cPrefix stInitial 222 (pState, pOutput) = runDFSTAction' cPrefix stInitial
214 (_, sOutput ) = runDFSTAction' cSuffix pState 223 (_, sOutput ) = runDFSTAction' cSuffix pState
215 (_, sOutput') = runDFSTAction' cSuffix' pState 224 (_, sOutput') = runDFSTAction' cSuffix' pState
@@ -237,13 +246,18 @@ dfstLens dfst@DFST{..} = EditLens ground propR propL
237 all = 0 Int.... max 246 all = 0 Int.... max
238 runCandidates :: Interval Natural -- ^ Departure from complement-run only permitted within interval (to guarantee locality) 247 runCandidates :: Interval Natural -- ^ Departure from complement-run only permitted within interval (to guarantee locality)
239 -> [(Seq ((Natural, (state, Maybe (input, Natural))), Maybe output), StringEdits input)] 248 -> [(Seq ((Natural, (state, Maybe (input, Natural))), Maybe output), StringEdits input)]
240 runCandidates ((,) <$> Int.inf <*> Int.sup -> (fInf, fSup)) = continueRun (Seq.empty, mempty) c 249 runCandidates focus = continueRun (Seq.empty, mempty) c 0
241 where 250 where
251 -- TODO: generate new complement
242 continueRun :: (Seq (LState state input output, Maybe output), StringEdits input) 252 continueRun :: (Seq (LState state input output, Maybe output), StringEdits input)
243 -> DFSTComplement state input output 253 -> DFSTComplement state input output
254 -> Natural -- ^ Input position
244 -> [(Seq (LState state input output, Maybe output), StringEdits input)] 255 -> [(Seq (LState state input output, Maybe output), StringEdits input)]
245 continueRun (run, inEdits) c' = do 256 continueRun (run, inEdits) c' inP = do
246 let 257 let
258 pos :: Natural
259 pos = fromIntegral $ Comp.length c - Comp.length c'
260 (c'', step) = Comp.splitAt (pred $ Comp.length c') c' -- TODO: unsafe
247 current :: LState state input output 261 current :: LState state input output
248 current 262 current
249 | Seq.Empty <- run = (0, (stInitial, Nothing)) 263 | Seq.Empty <- run = (0, (stInitial, Nothing))
@@ -251,30 +265,35 @@ dfstLens dfst@DFST{..} = EditLens ground propR propL
251 current' :: state 265 current' :: state
252 current' = let (_, (st, _)) = current 266 current' = let (_, (st, _)) = current
253 in st 267 in st
254 (c'', step) = Comp.splitAt (pred $ Comp.length c') c' -- TODO: unsafe
255 pos :: Natural
256 pos = fromIntegral $ Comp.length c - Comp.length c'
257 next' :: state 268 next' :: state
258 next' = fst . runDFSTAction' step $ current' 269 next' = fst . runDFSTAction' step $ current'
270 oldIn :: Maybe input
271 oldIn = Seq.lookup 0 $ dfstaConsumes' step
259 outgoing :: LState state input output -> [(LState state input output, Maybe input, Maybe output)] 272 outgoing :: LState state input output -> [(LState state input output, Maybe input, Maybe output)]
260 outgoing current = let go (st, minS) os acc 273 outgoing current = let go (st, minS) os acc
261 | st == current = ($ acc) $ Set.fold (\(st', moutS) -> (. ((st', minS, moutS) :))) id os 274 | st == current = ($ acc) $ Set.fold (\(st', moutS) -> (. ((st', minS, moutS) :))) id os
262 | otherwise = acc 275 | otherwise = acc
263 in Map.foldrWithKey go [] $ FST.stTransition outFST 276 in Map.foldrWithKey go [] $ FST.stTransition outFST
264 isPreferred :: (LState state input output, Maybe input, Maybe output) -> Bool 277 isPreferred :: (LState state input output, Maybe input, Maybe output) -> Bool
265 isPreferred ((_, (st, Nothing)), _, _) = st == next' 278 isPreferred ((_, (st, Nothing)), inS, _) = st == next' && (fromMaybe True $ (==) <$> oldIn <*> inS)
266 isPreferred (st, _, _) = any isPreferred $ outgoing st 279 isPreferred (st, _, _) = any isPreferred $ outgoing st
267 (preferred, alternate) = partition isPreferred $ outgoing current 280 (preferred, alternate) = partition isPreferred $ outgoing current
281 assocEdit :: (LState state input output, Maybe input, Maybe output) -> [(DFSTComplement state input output, StringEdits input, Natural)]
282 assocEdit (_, Just inS, _)
283 | oldIn == Just inS = [(c'', mempty, succ inP)]
284 | otherwise = [(c', insert inP inS, succ inP), (c'', insert inP inS <> delete inP, succ inP)]
285 assocEdit (_, Nothing, _) = [(c', mempty, inP)]
268 options 286 options
269 | pos >= fInf = preferred ++ alternate 287 | pos `Int.member` focus = preferred ++ alternate
270 | otherwise = preferred 288 | otherwise = preferred
271 (next, inS, outS) <- options 289 choice@(next, inS, outS) <- options
272 let acc = (run :> (next, outS), undefined {- TODO -}) 290 (c', inEdits', inP') <- assocEdit choice
273 bool id (acc :) (next `Set.member` FST.stAccept outFST) $ continueRun acc c'' 291 let acc = (run :> (next, outS), inEdits' <> inEdits)
292 bool id (acc :) (next `Set.member` FST.stAccept outFST) $ continueRun acc c' inP'
274 293
275 294
276 -- Properties of the edits computed are determined mostly by the order candidates are generated below 295 -- Properties of the edits computed are determined mostly by the order candidates are generated below
277 chosenRun <- listToMaybe . (\x -> trace (show $ map fst x) x) $ fragmentIntervals >>= runCandidates 296 chosenRun <- (\xs -> foldr (\x f -> x `seq` f) listToMaybe xs $ xs) $ traceShowId fragmentIntervals >>= (\x -> traceShowId <$> runCandidates x)
278 297
279 return $ traceShow chosenRun undefined 298 return $ traceShow chosenRun undefined
280 where 299 where