diff options
Diffstat (limited to 'edit-lens/src/Data/String/DFST/Lens.lhs')
-rw-r--r-- | edit-lens/src/Data/String/DFST/Lens.lhs | 31 |
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 | ||
5 | module Data.String.DFST.Lens | 6 | module Data.String.DFST.Lens |
@@ -14,6 +15,8 @@ module Data.String.DFST.Lens | |||
14 | 15 | ||
15 | import Data.String.DFST | 16 | import Data.String.DFST |
16 | import Control.Lens.Edit | 17 | import Control.Lens.Edit |
18 | import Control.Lens | ||
19 | import Control.Lens.TH | ||
17 | import Control.Edit | 20 | import Control.Edit |
18 | 21 | ||
19 | import Numeric.Natural | 22 | import Numeric.Natural |
@@ -27,20 +30,24 @@ import Data.Algorithm.Diff (Diff, getDiff) | |||
27 | import qualified Data.Algorithm.Diff as Diff | 30 | import qualified Data.Algorithm.Diff as Diff |
28 | 31 | ||
29 | import Data.Monoid | 32 | import Data.Monoid |
33 | import Data.Function (on) | ||
30 | 34 | ||
31 | 35 | ||
32 | data StringEdit = Insert Natural Char | 36 | data 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 | ||
36 | sePos :: StringEdit -> Natural | 40 | makeLenses ''StringEdit |
37 | sePos (Insert pos _) = pos | ||
38 | sePos (Delete pos ) = pos | ||
39 | 41 | ||
40 | data StringEdits = StringEdits (Seq StringEdit) | 42 | data StringEdits = StringEdits (Seq StringEdit) |
41 | | SEFail | 43 | | SEFail |
42 | deriving (Eq, Ord, Show, Read) | 44 | deriving (Eq, Ord, Show, Read) |
43 | 45 | ||
46 | makePrisms ''StringEdits | ||
47 | |||
48 | stringEdits :: Traversal' StringEdits StringEdit | ||
49 | stringEdits = _StringEdits . traverse | ||
50 | |||
44 | insert :: Natural -> Char -> StringEdits | 51 | insert :: Natural -> Char -> StringEdits |
45 | insert n c = StringEdits . Seq.singleton $ Insert n c | 52 | insert 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 | ||
143 | strDiff :: (String -> String) -> (String -> String) -> StringEdits | 148 | strDiff :: 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@ |
145 | strDiff a b = snd . foldr toEdit (0, mempty) $ getDiff (a []) (b []) | 150 | strDiff 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) |