diff options
Diffstat (limited to 'edit-lens/src/Control/DFST.lhs')
-rw-r--r-- | edit-lens/src/Control/DFST.lhs | 78 |
1 files changed, 78 insertions, 0 deletions
diff --git a/edit-lens/src/Control/DFST.lhs b/edit-lens/src/Control/DFST.lhs new file mode 100644 index 0000000..aec7bbb --- /dev/null +++ b/edit-lens/src/Control/DFST.lhs | |||
@@ -0,0 +1,78 @@ | |||
1 | \begin{code} | ||
2 | {-# LANGUAGE ScopedTypeVariables | ||
3 | #-} | ||
4 | |||
5 | {-| | ||
6 | Description: Deterministic finite state transducers | ||
7 | -} | ||
8 | module Control.DFST | ||
9 | ( DFST(..) | ||
10 | , runDFST, runDFST' | ||
11 | , toFST | ||
12 | ) where | ||
13 | |||
14 | import Data.Map.Strict (Map, (!?)) | ||
15 | import qualified Data.Map.Strict as Map | ||
16 | |||
17 | import Data.Set (Set) | ||
18 | import qualified Data.Set as Set | ||
19 | |||
20 | import Data.Sequence (Seq(..)) | ||
21 | import qualified Data.Sequence as Seq | ||
22 | |||
23 | import Data.Monoid | ||
24 | |||
25 | import Numeric.Natural | ||
26 | |||
27 | import Control.Monad | ||
28 | import Control.Monad.State | ||
29 | |||
30 | import Control.FST (FST(FST)) | ||
31 | import qualified Control.FST as FST | ||
32 | |||
33 | |||
34 | data DFST state input output = DFST | ||
35 | { stInitial :: state | ||
36 | , stTransition :: Map (state, input) (state, Seq output) | ||
37 | -- ^ All @(s, c)@-combinations not mapped are assumed to map to @(s, Nothing)@ | ||
38 | , stAccept :: Set state | ||
39 | } | ||
40 | |||
41 | |||
42 | toFST :: forall state input output. (Ord state, Ord input, Ord output) => DFST state input output -> FST (state, Natural) input output | ||
43 | -- ^ Split apart non-singleton outputs into a series of epsilon-transitions | ||
44 | -- | ||
45 | -- This function is currently invalid since multiple out-edges in the `DFST` visit the same intermediate states (we should label intermediate states not only with an ordinal but also with the input Symbol from the `DFST`) | ||
46 | toFST DFST{..} = flip execState initialFST $ forM_ (Map.toList stTransition) handleTransition | ||
47 | where | ||
48 | initialFST = FST | ||
49 | { stInitial = (stInitial, 0) | ||
50 | , stTransition = Map.empty | ||
51 | , stAccept = Set.map (,0) stAccept | ||
52 | } | ||
53 | addTransition :: forall state input output. (Ord state, Ord input, Ord output) => (state, Maybe input) -> (state, Maybe output) -> State (FST state input output) () | ||
54 | addTransition k v = modify $ \f@FST{ stTransition } -> f { FST.stTransition = Map.insertWith Set.union k (Set.singleton v) stTransition } | ||
55 | handleTransition :: ((state, input), (state, Seq output)) -> State (FST (state, Natural) input output) () | ||
56 | handleTransition ((st, inS), (st', outs)) = handleTransition' (st, 0) (Just inS) outs (st', 0) | ||
57 | handleTransition' :: (state, Natural) -> Maybe input -> Seq output -> (state, Natural) -> State (FST (state, Natural) input output) () | ||
58 | handleTransition' from inS Empty to = addTransition (from, inS) (to, Nothing) | ||
59 | handleTransition' from inS (outS :<| Empty) to = addTransition (from, inS) (to, Just outS) | ||
60 | handleTransition' from@(st, i) inS (outS :<| oo) to = addTransition (from, inS) ((st, succ i), Just outS) >> handleTransition' (st, succ i) Nothing oo to | ||
61 | |||
62 | runDFST :: forall state input output. (Ord state, Ord input) => DFST state input output -> Seq input -> Maybe (Seq output) | ||
63 | runDFST dfst@DFST{..} str = let (finalState, str') = runDFST' dfst stInitial str Seq.empty | ||
64 | in str' <$ guard (finalState `Set.member` stAccept) | ||
65 | |||
66 | runDFST' :: forall state input output. (Ord state, Ord input) | ||
67 | => DFST state input output | ||
68 | -> state -- ^ Current state | ||
69 | -> Seq input -- ^ Remaining input | ||
70 | -> Seq output -- ^ Accumulator containing previous output | ||
71 | -> (state, Seq output) -- ^ Next state, altered output | ||
72 | runDFST' _ st Empty acc = (st, acc) | ||
73 | runDFST' dfst@DFST{..} st (c :<| cs) acc | ||
74 | | Just (st', mc') <- stTransition !? (st, c) | ||
75 | = runDFST' dfst st' cs $ acc <> mc' | ||
76 | | otherwise | ||
77 | = runDFST' dfst st cs acc | ||
78 | \end{code} | ||