diff options
Diffstat (limited to 'edit-lens/src/Data/String/DFST')
| -rw-r--r-- | edit-lens/src/Data/String/DFST/Lens.lhs | 82 |
1 files changed, 82 insertions, 0 deletions
diff --git a/edit-lens/src/Data/String/DFST/Lens.lhs b/edit-lens/src/Data/String/DFST/Lens.lhs new file mode 100644 index 0000000..52c80d0 --- /dev/null +++ b/edit-lens/src/Data/String/DFST/Lens.lhs | |||
| @@ -0,0 +1,82 @@ | |||
| 1 | \begin{code} | ||
| 2 | {-# LANGUAGE TupleSections | ||
| 3 | #-} | ||
| 4 | |||
| 5 | module Data.String.DFST.Lens | ||
| 6 | ( | ||
| 7 | ) where | ||
| 8 | |||
| 9 | import Data.String.DFST | ||
| 10 | import Control.Lens.Edit | ||
| 11 | import Control.Edit | ||
| 12 | |||
| 13 | import Numeric.Natural | ||
| 14 | import Data.Sequence (Seq((:<|), (:|>))) | ||
| 15 | import qualified Data.Sequence as Seq | ||
| 16 | |||
| 17 | data StringEdit = Insert Natural Char | ||
| 18 | | Delete Natural | ||
| 19 | deriving (Eq, Ord, Show, Read) | ||
| 20 | |||
| 21 | data StringEdits = StringEdits (Seq StringEdit) | ||
| 22 | | SEFail | ||
| 23 | deriving (Eq, Ord, Show, Read) | ||
| 24 | |||
| 25 | insert :: Natural -> Char -> StringEdits | ||
| 26 | insert n c = StringEdits . Seq.singleton $ Insert n c | ||
| 27 | |||
| 28 | delete :: Natural -> StringEdits | ||
| 29 | delete n = StringEdits . Seq.singleton $ Delete n | ||
| 30 | |||
| 31 | instance Monoid StringEdits where | ||
| 32 | mempty = StringEdits Seq.empty | ||
| 33 | SEFail `mappend` _ = SEFail | ||
| 34 | _ `mappend` SEFail = SEFail | ||
| 35 | (StringEdits Seq.Empty) `mappend` x = x | ||
| 36 | x `mappend` (StringEdits Seq.Empty) = x | ||
| 37 | (StringEdits x@(bs :|> b)) `mappend` (StringEdits y@(a :<| as)) | ||
| 38 | | (Insert n _) <- a | ||
| 39 | , (Delete n') <- b | ||
| 40 | , n == n' | ||
| 41 | = StringEdits bs `mappend` StringEdits as | ||
| 42 | | otherwise = StringEdits $ x `mappend` y | ||
| 43 | |||
| 44 | instance Module StringEdits where | ||
| 45 | type Domain StringEdits = String | ||
| 46 | apply str SEFail = Nothing | ||
| 47 | apply str (StringEdits Seq.Empty) = Just str | ||
| 48 | apply str (StringEdits (es :|> Insert n c)) = (flip apply) (StringEdits es) =<< go str n c | ||
| 49 | where | ||
| 50 | go [] n c | ||
| 51 | | n == 0 = Just [c] | ||
| 52 | | otherwise = Nothing | ||
| 53 | go str@(x:xs) n c | ||
| 54 | | n == 0 = Just $ c : str | ||
| 55 | | otherwise = (x:) <$> go xs (pred n) c | ||
| 56 | apply str (StringEdits (es :|> Delete n)) = (flip apply) (StringEdits es) =<< go str n | ||
| 57 | where | ||
| 58 | go [] _ = Nothing | ||
| 59 | go (x:xs) n | ||
| 60 | | n == 0 = Just xs | ||
| 61 | | otherwise = (x:) <$> go xs (pred n) | ||
| 62 | |||
| 63 | init = "" | ||
| 64 | divInit = StringEdits . Seq.unfoldl go . (0,) | ||
| 65 | where | ||
| 66 | go (_, []) = Nothing | ||
| 67 | go (n, (c:cs)) = Just ((succ n, cs), Insert n c) | ||
| 68 | |||
| 69 | data DFSTAction state = DFSTBranch (Map state (state, String)) (DFSTAction state) (DFSTAction state) | ||
| 70 | | DFSTLeaf | ||
| 71 | |||
| 72 | dfstLens :: forall state. Ord state => DFST state -> EditLens (DFSTAction state) StringEdits StringEdits | ||
| 73 | dfstLens DFST{..} = EditLens ground propR propL | ||
| 74 | where | ||
| 75 | ground :: DFSTAction state | ||
| 76 | ground = DFSTLeaf | ||
| 77 | |||
| 78 | propR :: (DFSTAction state, StringEdits) -> (DFSTAction state, StringEdits) | ||
| 79 | propR = undefined | ||
| 80 | propL :: (DFSTAction state, StringEdits) -> (DFSTAction state, StringEdits) | ||
| 81 | propL = undefined | ||
| 82 | \end{code} | ||
