summaryrefslogtreecommitdiff
path: root/edit-lens/src/Data
diff options
context:
space:
mode:
Diffstat (limited to 'edit-lens/src/Data')
-rw-r--r--edit-lens/src/Data/String/DFST/Lens.lhs31
1 files changed, 18 insertions, 13 deletions
diff --git a/edit-lens/src/Data/String/DFST/Lens.lhs b/edit-lens/src/Data/String/DFST/Lens.lhs
index 9def01b..8fd748a 100644
--- a/edit-lens/src/Data/String/DFST/Lens.lhs
+++ b/edit-lens/src/Data/String/DFST/Lens.lhs
@@ -1,5 +1,6 @@
1\begin{code} 1\begin{code}
2{-# LANGUAGE ScopedTypeVariables 2{-# LANGUAGE ScopedTypeVariables
3 , TemplateHaskell
3#-} 4#-}
4 5
5module Data.String.DFST.Lens 6module Data.String.DFST.Lens
@@ -14,6 +15,8 @@ module Data.String.DFST.Lens
14 15
15import Data.String.DFST 16import Data.String.DFST
16import Control.Lens.Edit 17import Control.Lens.Edit
18import Control.Lens
19import Control.Lens.TH
17import Control.Edit 20import Control.Edit
18 21
19import Numeric.Natural 22import Numeric.Natural
@@ -27,20 +30,24 @@ import Data.Algorithm.Diff (Diff, getDiff)
27import qualified Data.Algorithm.Diff as Diff 30import qualified Data.Algorithm.Diff as Diff
28 31
29import Data.Monoid 32import Data.Monoid
33import Data.Function (on)
30 34
31 35
32data StringEdit = Insert Natural Char 36data StringEdit = Insert { _sePos :: Natural, _seInsertion :: Char }
33 | Delete Natural 37 | Delete { _sePos :: Natural }
34 deriving (Eq, Ord, Show, Read) 38 deriving (Eq, Ord, Show, Read)
35 39
36sePos :: StringEdit -> Natural 40makeLenses ''StringEdit
37sePos (Insert pos _) = pos
38sePos (Delete pos ) = pos
39 41
40data StringEdits = StringEdits (Seq StringEdit) 42data StringEdits = StringEdits (Seq StringEdit)
41 | SEFail 43 | SEFail
42 deriving (Eq, Ord, Show, Read) 44 deriving (Eq, Ord, Show, Read)
43 45
46makePrisms ''StringEdits
47
48stringEdits :: Traversal' StringEdits StringEdit
49stringEdits = _StringEdits . traverse
50
44insert :: Natural -> Char -> StringEdits 51insert :: Natural -> Char -> StringEdits
45insert n c = StringEdits . Seq.singleton $ Insert n c 52insert n c = StringEdits . Seq.singleton $ Insert n c
46 53
@@ -121,9 +128,9 @@ dfstLens dfst@DFST{..} = EditLens ground propR propL
121 128
122 propR :: (DFSTComplement state, StringEdits) -> (DFSTComplement state, StringEdits) 129 propR :: (DFSTComplement state, StringEdits) -> (DFSTComplement state, StringEdits)
123 propR (c, SEFail) = (c, SEFail) 130 propR (c, SEFail) = (c, SEFail)
124 propR (c, StringEdits (es :|> e)) = (c', es' <> shiftBy (length $ pOutput []) (strDiff sOutput sOutput')) 131 propR (c, StringEdits (es :|> e)) = (c', es' <> es'')
125 where 132 where
126 (cSuffix, cPrefix) = Comp.splitAt (Comp.length c - (fromEnum $ sePos e)) c 133 (cSuffix, cPrefix) = Comp.splitAt (Comp.length c - (e ^. sePos . from enum)) c
127 cSuffix' 134 cSuffix'
128 | Delete _ <- e = Comp.take (pred $ Comp.length cSuffix) cSuffix -- TODO unsafe 135 | Delete _ <- e = Comp.take (pred $ Comp.length cSuffix) cSuffix -- TODO unsafe
129 | Insert _ nChar <- e = cSuffix <> Comp.singleton (DFSTAction $ \x -> runDFST' dfst x (pure nChar) id) 136 | Insert _ nChar <- e = cSuffix <> Comp.singleton (DFSTAction $ \x -> runDFST' dfst x (pure nChar) id)
@@ -131,18 +138,16 @@ dfstLens dfst@DFST{..} = EditLens ground propR propL
131 (_, sOutput ) = runDFSTAction (Comp.composed cSuffix ) pState 138 (_, sOutput ) = runDFSTAction (Comp.composed cSuffix ) pState
132 (_, sOutput') = runDFSTAction (Comp.composed cSuffix') pState 139 (_, sOutput') = runDFSTAction (Comp.composed cSuffix') pState
133 (c', es') = propR (cSuffix' <> cPrefix, StringEdits es) 140 (c', es') = propR (cSuffix' <> cPrefix, StringEdits es)
134 shiftBy (toEnum -> n) (StringEdits es) = StringEdits $ shiftBy' n <$> es 141 es'' = (strDiff `on` ($ "")) sOutput sOutput' & stringEdits . sePos . from enum +~ (length $ pOutput [])
135 shiftBy' n' (Insert n c) = Insert (n + n') c
136 shiftBy' n' (Delete n) = Delete (n + n')
137 propR (c, mempty) = (c, mempty) 142 propR (c, mempty) = (c, mempty)
138 143
139 144
140 propL :: (DFSTComplement state, StringEdits) -> (DFSTComplement state, StringEdits) 145 propL :: (DFSTComplement state, StringEdits) -> (DFSTComplement state, StringEdits)
141 propL = undefined 146 propL = undefined
142 147
143strDiff :: (String -> String) -> (String -> String) -> StringEdits 148strDiff :: String -> String -> StringEdits
144-- ^ @strDiff a b@ calculates a set of edits, which, when applied to @a@, produce @b@, where both @a@ and @b@ are given as diff-lists of chars 149-- ^ @strDiff a b@ calculates a set of edits, which, when applied to @a@, produce @b@
145strDiff a b = snd . foldr toEdit (0, mempty) $ getDiff (a []) (b []) 150strDiff a b = snd . foldr toEdit (0, mempty) $ getDiff a b
146 where 151 where
147 toEdit :: Diff Char -> (Natural, StringEdits) -> (Natural, StringEdits) 152 toEdit :: Diff Char -> (Natural, StringEdits) -> (Natural, StringEdits)
148 toEdit (Diff.Both _ _) (n, es) = (succ n, es) 153 toEdit (Diff.Both _ _) (n, es) = (succ n, es)