summaryrefslogtreecommitdiff
path: root/edit-lens/src/Control
diff options
context:
space:
mode:
Diffstat (limited to 'edit-lens/src/Control')
-rw-r--r--edit-lens/src/Control/DFST.lhs2
-rw-r--r--edit-lens/src/Control/FST.lhs114
2 files changed, 113 insertions, 3 deletions
diff --git a/edit-lens/src/Control/DFST.lhs b/edit-lens/src/Control/DFST.lhs
index 94df533..9bd1629 100644
--- a/edit-lens/src/Control/DFST.lhs
+++ b/edit-lens/src/Control/DFST.lhs
@@ -46,7 +46,7 @@ toFST :: forall state input output. (Ord state, Ord input, Ord output) => DFST s
46toFST DFST{..} = flip execState initialFST $ forM_ (Map.toList stTransition) handleTransition 46toFST DFST{..} = flip execState initialFST $ forM_ (Map.toList stTransition) handleTransition
47 where 47 where
48 initialFST = FST 48 initialFST = FST
49 { stInitial = (stInitial, Nothing) 49 { stInitial = Set.singleton (stInitial, Nothing)
50 , stTransition = Map.empty 50 , stTransition = Map.empty
51 , stAccept = Set.map (, Nothing) stAccept 51 , stAccept = Set.map (, Nothing) stAccept
52 } 52 }
diff --git a/edit-lens/src/Control/FST.lhs b/edit-lens/src/Control/FST.lhs
index d3c8ca9..d37072f 100644
--- a/edit-lens/src/Control/FST.lhs
+++ b/edit-lens/src/Control/FST.lhs
@@ -1,24 +1,134 @@
1\begin{code} 1\begin{code}
2{-# LANGUAGE ScopedTypeVariables
3#-}
2 4
3{-| 5{-|
4Description: Finite state transducers with epsilon-transitions 6Description: Finite state transducers with epsilon-transitions
5-} 7-}
6module Control.FST 8module Control.FST
7 ( FST(..) 9 ( FST(..)
10 -- * Constructing FSTs
11 , wordFST
12 -- * Operations on FSTs
13 , productFST, invertFST, restrictFST
14 -- * Debugging Utilities
15 , liveFST
8 ) where 16 ) where
9 17
10import Data.Map.Strict (Map) 18import Data.Map.Strict (Map, (!?))
11import qualified Data.Map.Strict as Map 19import qualified Data.Map.Strict as Map
12 20
13import Data.Set (Set) 21import Data.Set (Set)
22import qualified Data.Set as Set
14 23
15import Data.Sequence (Seq) 24import Data.Sequence (Seq)
25import qualified Data.Sequence as Seq
26
27import Data.Maybe (mapMaybe, fromMaybe)
28
29import Numeric.Natural
16 30
17import Control.Lens.TH 31import Control.Lens.TH
18 32
33import Control.Monad.State.Strict
34
35import Text.PrettyPrint.Leijen (Pretty(..))
36import qualified Text.PrettyPrint.Leijen as PP
37
38import Debug.Trace
39
19data FST state input output = FST 40data FST state input output = FST
20 { stInitial :: state 41 { stInitial :: Set state
21 , stTransition :: Map (state, Maybe input) (Set (state, Maybe output)) 42 , stTransition :: Map (state, Maybe input) (Set (state, Maybe output))
22 , stAccept :: Set state 43 , stAccept :: Set state
44 } deriving (Show, Read)
45
46instance (Show state, Show input, Show output) => Pretty (FST state input output) where
47 pretty FST{..} = PP.vsep
48 [ PP.text "Initial states:" PP.</> PP.hang 2 (PP.list . map (PP.text . show) $ Set.toAscList stInitial)
49 , PP.text "State transitions:" PP.<$> PP.indent 2 (PP.vsep
50 [ PP.text (show st)
51 PP.<+> (PP.text "-" PP.<> PP.tupled [label inS, label outS] PP.<> PP.text "→")
52 PP.<+> PP.text (show st')
53 | ((st, inS), to) <- Map.toList stTransition
54 , (st', outS) <- Set.toAscList to
55 ])
56 , PP.text "Accepting states:" PP.</> PP.hang 2 (PP.list . map (PP.text . show) $ Set.toAscList stAccept)
57 ]
58 where
59 label :: Show a => Maybe a -> PP.Doc
60 label = maybe (PP.text "ɛ") (PP.text . show)
61
62wordFST :: forall input output. Seq output -> FST Natural input output
63-- ^ @wordFST str@ is the minimal FST generating @str@ as output when given no input
64wordFST outs = FST
65 { stInitial = Set.singleton 0
66 , stAccept = Set.singleton l
67 , stTransition = Map.fromSet next states
23 } 68 }
69 where
70 l :: Natural
71 l = fromIntegral $ Seq.length outs
72 states :: Set (Natural, Maybe input)
73 states = Set.fromDistinctAscList [ (n, Nothing) | n <- [0..pred l] ]
74 next :: (Natural, Maybe input) -> Set (Natural, Maybe output)
75 next (i, _) = Set.singleton (succ i, Just . Seq.index outs $ fromIntegral i)
76
77productFST :: forall state1 state2 input output. (Ord state1, Ord state2, Ord input, Ord output) => FST state1 input output -> FST state2 input output -> FST (state1, state2) input output
78-- ^ Cartesian product on states, logical conjunction on transitions and state-properties (initial and accept)
79--
80-- This is most intuitive when thought of as the component-wise product of weighted FSTs with weights in the boolean semiring.
81productFST fst1 fst2 = FST
82 { stInitial = stInitial fst1 `setProduct` stInitial fst2
83 , stAccept = stAccept fst1 `setProduct` stAccept fst2
84 , stTransition = Map.fromSet transitions . Set.fromList . mapMaybe filterTransition . Set.toAscList $ Map.keysSet (stTransition fst1) `setProduct` Map.keysSet (stTransition fst2)
85 }
86 where
87 setProduct :: forall a b. Set a -> Set b -> Set (a, b)
88 setProduct as bs = Set.fromDistinctAscList $ (,) <$> Set.toAscList as <*> Set.toAscList bs
89 filterTransition :: forall label. Eq label => ((state1, Maybe label), (state2, Maybe label)) -> Maybe ((state1, state2), Maybe label)
90 filterTransition ((st1, Nothing ), (st2, in2 )) = Just ((st1, st2), in2)
91 filterTransition ((st1, in1 ), (st2, Nothing )) = Just ((st1, st2), in1)
92 filterTransition ((st1, Just in1), (st2, Just in2))
93 | in1 == in2 = Just ((st1, st2), Just in1)
94 | otherwise = Nothing
95 transitions :: ((state1, state2), Maybe input) -> Set ((state1, state2), Maybe output)
96 transitions ((st1, st2), inS) = Set.fromList . mapMaybe filterTransition . Set.toAscList $ out1 `setProduct` out2
97 where
98 out1 = (fromMaybe Set.empty $ stTransition fst1 !? (st1, inS)) `Set.union` (fromMaybe Set.empty $ stTransition fst1 !? (st1, Nothing))
99 out2 = (fromMaybe Set.empty $ stTransition fst2 !? (st2, inS)) `Set.union` (fromMaybe Set.empty $ stTransition fst2 !? (st2, Nothing))
100
101restrictFST :: forall state input output. (Ord state, Ord input, Ord output) => Set state -> FST state input output -> FST state input output
102restrictFST sts FST{..} = FST
103 { stInitial = stInitial `Set.intersection` sts
104 , stAccept = stAccept `Set.intersection` sts
105 , stTransition = Map.mapMaybeWithKey restrictTransition stTransition
106 }
107 where
108 restrictTransition :: (state, Maybe input) -> Set (state, Maybe output) -> Maybe (Set (state, Maybe output))
109 restrictTransition (st, _) tos = tos' <$ guard (st `Set.member` sts)
110 where
111 tos' = Set.filter (\(st', _) -> st' `Set.member` sts) tos
112
113
114liveFST :: forall state input output. (Ord state, Ord input, Ord output, Show state) => FST state input output -> Set state
115-- ^ Compute the set of "live" states (with no particular complexity)
116--
117-- A state is "live" iff there is a path from it to an accepting state and a path from an initial state to it
118liveFST fst@FST{..} = flip execState Set.empty $ mapM_ (depthSearch Set.empty) stInitial
119 where
120 stTransition' :: Map state (Set state)
121 stTransition' = Map.map (Set.map $ \(st, _) -> st) $ Map.mapKeysWith Set.union (\(st, _) -> st) stTransition
122 depthSearch :: Set state -> state -> State (Set state) ()
123 depthSearch acc curr = do
124 let acc' = Set.insert curr acc
125 next = fromMaybe Set.empty $ stTransition' !? curr
126 alreadyLive <- get
127 when (not . Set.null $ Set.insert curr next `Set.intersection` Set.union stAccept alreadyLive) $
128 modify $ Set.union acc'
129 mapM_ (depthSearch acc') $ next `Set.difference` alreadyLive
130
131
132invertFST :: FST state input output -> Seq output -> Set (Seq input)
133invertFST = undefined
24\end{code} 134\end{code}