{-# LANGUAGE LambdaCase, ScopedTypeVariables #-} module DebuggingTMTypes where import TuringMachine import TuringMachine.Optimization import GrammarType import Control.Monad (forM) newtype DebuggingState = DState String deriving (DebuggingState -> DebuggingState -> Bool (DebuggingState -> DebuggingState -> Bool) -> (DebuggingState -> DebuggingState -> Bool) -> Eq DebuggingState forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: DebuggingState -> DebuggingState -> Bool $c/= :: DebuggingState -> DebuggingState -> Bool == :: DebuggingState -> DebuggingState -> Bool $c== :: DebuggingState -> DebuggingState -> Bool Eq, Eq DebuggingState Eq DebuggingState -> (DebuggingState -> DebuggingState -> Ordering) -> (DebuggingState -> DebuggingState -> Bool) -> (DebuggingState -> DebuggingState -> Bool) -> (DebuggingState -> DebuggingState -> Bool) -> (DebuggingState -> DebuggingState -> Bool) -> (DebuggingState -> DebuggingState -> DebuggingState) -> (DebuggingState -> DebuggingState -> DebuggingState) -> Ord DebuggingState DebuggingState -> DebuggingState -> Bool DebuggingState -> DebuggingState -> Ordering DebuggingState -> DebuggingState -> DebuggingState forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: DebuggingState -> DebuggingState -> DebuggingState $cmin :: DebuggingState -> DebuggingState -> DebuggingState max :: DebuggingState -> DebuggingState -> DebuggingState $cmax :: DebuggingState -> DebuggingState -> DebuggingState >= :: DebuggingState -> DebuggingState -> Bool $c>= :: DebuggingState -> DebuggingState -> Bool > :: DebuggingState -> DebuggingState -> Bool $c> :: DebuggingState -> DebuggingState -> Bool <= :: DebuggingState -> DebuggingState -> Bool $c<= :: DebuggingState -> DebuggingState -> Bool < :: DebuggingState -> DebuggingState -> Bool $c< :: DebuggingState -> DebuggingState -> Bool compare :: DebuggingState -> DebuggingState -> Ordering $ccompare :: DebuggingState -> DebuggingState -> Ordering $cp1Ord :: Eq DebuggingState Ord, Int -> DebuggingState -> ShowS [DebuggingState] -> ShowS DebuggingState -> String (Int -> DebuggingState -> ShowS) -> (DebuggingState -> String) -> ([DebuggingState] -> ShowS) -> Show DebuggingState forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [DebuggingState] -> ShowS $cshowList :: [DebuggingState] -> ShowS show :: DebuggingState -> String $cshow :: DebuggingState -> String showsPrec :: Int -> DebuggingState -> ShowS $cshowsPrec :: Int -> DebuggingState -> ShowS Show) newtype DebuggingSymbol = DSymbol { DebuggingSymbol -> String unDSymbol :: String } deriving (DebuggingSymbol -> DebuggingSymbol -> Bool (DebuggingSymbol -> DebuggingSymbol -> Bool) -> (DebuggingSymbol -> DebuggingSymbol -> Bool) -> Eq DebuggingSymbol forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: DebuggingSymbol -> DebuggingSymbol -> Bool $c/= :: DebuggingSymbol -> DebuggingSymbol -> Bool == :: DebuggingSymbol -> DebuggingSymbol -> Bool $c== :: DebuggingSymbol -> DebuggingSymbol -> Bool Eq, Eq DebuggingSymbol Eq DebuggingSymbol -> (DebuggingSymbol -> DebuggingSymbol -> Ordering) -> (DebuggingSymbol -> DebuggingSymbol -> Bool) -> (DebuggingSymbol -> DebuggingSymbol -> Bool) -> (DebuggingSymbol -> DebuggingSymbol -> Bool) -> (DebuggingSymbol -> DebuggingSymbol -> Bool) -> (DebuggingSymbol -> DebuggingSymbol -> DebuggingSymbol) -> (DebuggingSymbol -> DebuggingSymbol -> DebuggingSymbol) -> Ord DebuggingSymbol DebuggingSymbol -> DebuggingSymbol -> Bool DebuggingSymbol -> DebuggingSymbol -> Ordering DebuggingSymbol -> DebuggingSymbol -> DebuggingSymbol forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: DebuggingSymbol -> DebuggingSymbol -> DebuggingSymbol $cmin :: DebuggingSymbol -> DebuggingSymbol -> DebuggingSymbol max :: DebuggingSymbol -> DebuggingSymbol -> DebuggingSymbol $cmax :: DebuggingSymbol -> DebuggingSymbol -> DebuggingSymbol >= :: DebuggingSymbol -> DebuggingSymbol -> Bool $c>= :: DebuggingSymbol -> DebuggingSymbol -> Bool > :: DebuggingSymbol -> DebuggingSymbol -> Bool $c> :: DebuggingSymbol -> DebuggingSymbol -> Bool <= :: DebuggingSymbol -> DebuggingSymbol -> Bool $c<= :: DebuggingSymbol -> DebuggingSymbol -> Bool < :: DebuggingSymbol -> DebuggingSymbol -> Bool $c< :: DebuggingSymbol -> DebuggingSymbol -> Bool compare :: DebuggingSymbol -> DebuggingSymbol -> Ordering $ccompare :: DebuggingSymbol -> DebuggingSymbol -> Ordering $cp1Ord :: Eq DebuggingSymbol Ord, Int -> DebuggingSymbol -> ShowS [DebuggingSymbol] -> ShowS DebuggingSymbol -> String (Int -> DebuggingSymbol -> ShowS) -> (DebuggingSymbol -> String) -> ([DebuggingSymbol] -> ShowS) -> Show DebuggingSymbol forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [DebuggingSymbol] -> ShowS $cshowList :: [DebuggingSymbol] -> ShowS show :: DebuggingSymbol -> String $cshow :: DebuggingSymbol -> String showsPrec :: Int -> DebuggingSymbol -> ShowS $cshowsPrec :: Int -> DebuggingSymbol -> ShowS Show) data DebuggingMove = D DebuggingSymbol | L | R deriving (DebuggingMove -> DebuggingMove -> Bool (DebuggingMove -> DebuggingMove -> Bool) -> (DebuggingMove -> DebuggingMove -> Bool) -> Eq DebuggingMove forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: DebuggingMove -> DebuggingMove -> Bool $c/= :: DebuggingMove -> DebuggingMove -> Bool == :: DebuggingMove -> DebuggingMove -> Bool $c== :: DebuggingMove -> DebuggingMove -> Bool Eq, Eq DebuggingMove Eq DebuggingMove -> (DebuggingMove -> DebuggingMove -> Ordering) -> (DebuggingMove -> DebuggingMove -> Bool) -> (DebuggingMove -> DebuggingMove -> Bool) -> (DebuggingMove -> DebuggingMove -> Bool) -> (DebuggingMove -> DebuggingMove -> Bool) -> (DebuggingMove -> DebuggingMove -> DebuggingMove) -> (DebuggingMove -> DebuggingMove -> DebuggingMove) -> Ord DebuggingMove DebuggingMove -> DebuggingMove -> Bool DebuggingMove -> DebuggingMove -> Ordering DebuggingMove -> DebuggingMove -> DebuggingMove forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: DebuggingMove -> DebuggingMove -> DebuggingMove $cmin :: DebuggingMove -> DebuggingMove -> DebuggingMove max :: DebuggingMove -> DebuggingMove -> DebuggingMove $cmax :: DebuggingMove -> DebuggingMove -> DebuggingMove >= :: DebuggingMove -> DebuggingMove -> Bool $c>= :: DebuggingMove -> DebuggingMove -> Bool > :: DebuggingMove -> DebuggingMove -> Bool $c> :: DebuggingMove -> DebuggingMove -> Bool <= :: DebuggingMove -> DebuggingMove -> Bool $c<= :: DebuggingMove -> DebuggingMove -> Bool < :: DebuggingMove -> DebuggingMove -> Bool $c< :: DebuggingMove -> DebuggingMove -> Bool compare :: DebuggingMove -> DebuggingMove -> Ordering $ccompare :: DebuggingMove -> DebuggingMove -> Ordering $cp1Ord :: Eq DebuggingMove Ord, Int -> DebuggingMove -> ShowS [DebuggingMove] -> ShowS DebuggingMove -> String (Int -> DebuggingMove -> ShowS) -> (DebuggingMove -> String) -> ([DebuggingMove] -> ShowS) -> Show DebuggingMove forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [DebuggingMove] -> ShowS $cshowList :: [DebuggingMove] -> ShowS show :: DebuggingMove -> String $cshow :: DebuggingMove -> String showsPrec :: Int -> DebuggingMove -> ShowS $cshowsPrec :: Int -> DebuggingMove -> ShowS Show) newtype DebuggingQuadruples = DQuadruples (Map (DebuggingState, DebuggingSymbol) (DebuggingMove, DebuggingState)) deriving (DebuggingQuadruples -> DebuggingQuadruples -> Bool (DebuggingQuadruples -> DebuggingQuadruples -> Bool) -> (DebuggingQuadruples -> DebuggingQuadruples -> Bool) -> Eq DebuggingQuadruples forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: DebuggingQuadruples -> DebuggingQuadruples -> Bool $c/= :: DebuggingQuadruples -> DebuggingQuadruples -> Bool == :: DebuggingQuadruples -> DebuggingQuadruples -> Bool $c== :: DebuggingQuadruples -> DebuggingQuadruples -> Bool Eq, Eq DebuggingQuadruples Eq DebuggingQuadruples -> (DebuggingQuadruples -> DebuggingQuadruples -> Ordering) -> (DebuggingQuadruples -> DebuggingQuadruples -> Bool) -> (DebuggingQuadruples -> DebuggingQuadruples -> Bool) -> (DebuggingQuadruples -> DebuggingQuadruples -> Bool) -> (DebuggingQuadruples -> DebuggingQuadruples -> Bool) -> (DebuggingQuadruples -> DebuggingQuadruples -> DebuggingQuadruples) -> (DebuggingQuadruples -> DebuggingQuadruples -> DebuggingQuadruples) -> Ord DebuggingQuadruples DebuggingQuadruples -> DebuggingQuadruples -> Bool DebuggingQuadruples -> DebuggingQuadruples -> Ordering DebuggingQuadruples -> DebuggingQuadruples -> DebuggingQuadruples forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: DebuggingQuadruples -> DebuggingQuadruples -> DebuggingQuadruples $cmin :: DebuggingQuadruples -> DebuggingQuadruples -> DebuggingQuadruples max :: DebuggingQuadruples -> DebuggingQuadruples -> DebuggingQuadruples $cmax :: DebuggingQuadruples -> DebuggingQuadruples -> DebuggingQuadruples >= :: DebuggingQuadruples -> DebuggingQuadruples -> Bool $c>= :: DebuggingQuadruples -> DebuggingQuadruples -> Bool > :: DebuggingQuadruples -> DebuggingQuadruples -> Bool $c> :: DebuggingQuadruples -> DebuggingQuadruples -> Bool <= :: DebuggingQuadruples -> DebuggingQuadruples -> Bool $c<= :: DebuggingQuadruples -> DebuggingQuadruples -> Bool < :: DebuggingQuadruples -> DebuggingQuadruples -> Bool $c< :: DebuggingQuadruples -> DebuggingQuadruples -> Bool compare :: DebuggingQuadruples -> DebuggingQuadruples -> Ordering $ccompare :: DebuggingQuadruples -> DebuggingQuadruples -> Ordering $cp1Ord :: Eq DebuggingQuadruples Ord, Int -> DebuggingQuadruples -> ShowS [DebuggingQuadruples] -> ShowS DebuggingQuadruples -> String (Int -> DebuggingQuadruples -> ShowS) -> (DebuggingQuadruples -> String) -> ([DebuggingQuadruples] -> ShowS) -> Show DebuggingQuadruples forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [DebuggingQuadruples] -> ShowS $cshowList :: [DebuggingQuadruples] -> ShowS show :: DebuggingQuadruples -> String $cshow :: DebuggingQuadruples -> String showsPrec :: Int -> DebuggingQuadruples -> ShowS $cshowsPrec :: Int -> DebuggingQuadruples -> ShowS Show) newtype DebuggingTuringMachine = DTM DebuggingQuadruples deriving (Int -> DebuggingTuringMachine -> ShowS [DebuggingTuringMachine] -> ShowS DebuggingTuringMachine -> String (Int -> DebuggingTuringMachine -> ShowS) -> (DebuggingTuringMachine -> String) -> ([DebuggingTuringMachine] -> ShowS) -> Show DebuggingTuringMachine forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [DebuggingTuringMachine] -> ShowS $cshowList :: [DebuggingTuringMachine] -> ShowS show :: DebuggingTuringMachine -> String $cshow :: DebuggingTuringMachine -> String showsPrec :: Int -> DebuggingTuringMachine -> ShowS $cshowsPrec :: Int -> DebuggingTuringMachine -> ShowS Show, DebuggingTuringMachine -> DebuggingTuringMachine -> Bool (DebuggingTuringMachine -> DebuggingTuringMachine -> Bool) -> (DebuggingTuringMachine -> DebuggingTuringMachine -> Bool) -> Eq DebuggingTuringMachine forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: DebuggingTuringMachine -> DebuggingTuringMachine -> Bool $c/= :: DebuggingTuringMachine -> DebuggingTuringMachine -> Bool == :: DebuggingTuringMachine -> DebuggingTuringMachine -> Bool $c== :: DebuggingTuringMachine -> DebuggingTuringMachine -> Bool Eq) finalDState :: DebuggingState finalDState :: DebuggingState finalDState = String -> DebuggingState DState String "accepted" startDState :: DebuggingState startDState :: DebuggingState startDState = String -> DebuggingState DState String "qWriteStartCounter" newtype SymbolsPair = SymbolsPair (Nonterminal, Int, Bool, GrammarType.Symbol, GrammarType.Symbol) deriving (SymbolsPair -> SymbolsPair -> Bool (SymbolsPair -> SymbolsPair -> Bool) -> (SymbolsPair -> SymbolsPair -> Bool) -> Eq SymbolsPair forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: SymbolsPair -> SymbolsPair -> Bool $c/= :: SymbolsPair -> SymbolsPair -> Bool == :: SymbolsPair -> SymbolsPair -> Bool $c== :: SymbolsPair -> SymbolsPair -> Bool Eq, Int -> SymbolsPair -> ShowS [SymbolsPair] -> ShowS SymbolsPair -> String (Int -> SymbolsPair -> ShowS) -> (SymbolsPair -> String) -> ([SymbolsPair] -> ShowS) -> Show SymbolsPair forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [SymbolsPair] -> ShowS $cshowList :: [SymbolsPair] -> ShowS show :: SymbolsPair -> String $cshow :: SymbolsPair -> String showsPrec :: Int -> SymbolsPair -> ShowS $cshowsPrec :: Int -> SymbolsPair -> ShowS Show) convertToTuringMachine :: MonadFail m => DebuggingTuringMachine -> m TuringMachine convertToTuringMachine :: DebuggingTuringMachine -> m TuringMachine convertToTuringMachine tm :: DebuggingTuringMachine tm@(DTM (DQuadruples Map (DebuggingState, DebuggingSymbol) (DebuggingMove, DebuggingState) quadruplesMap)) = do let states' :: IsoMap DebuggingState State states' = DebuggingTuringMachine -> IsoMap DebuggingState State getStates DebuggingTuringMachine tm (Alphabet alphabet', IsoMap DebuggingSymbol Symbol symbols') = DebuggingTuringMachine -> (Alphabet, IsoMap DebuggingSymbol Symbol) getSymbols DebuggingTuringMachine tm [((State, Symbol), (MoveOr Symbol, State))] quadruplesList <- [((DebuggingState, DebuggingSymbol), (DebuggingMove, DebuggingState))] -> (((DebuggingState, DebuggingSymbol), (DebuggingMove, DebuggingState)) -> m ((State, Symbol), (MoveOr Symbol, State))) -> m [((State, Symbol), (MoveOr Symbol, State))] forall (t :: * -> *) (m :: * -> *) a b. (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b) forM (Map (DebuggingState, DebuggingSymbol) (DebuggingMove, DebuggingState) -> [((DebuggingState, DebuggingSymbol), (DebuggingMove, DebuggingState))] forall c v. Listable c v => c -> [v] toList Map (DebuggingState, DebuggingSymbol) (DebuggingMove, DebuggingState) quadruplesMap) ((((DebuggingState, DebuggingSymbol), (DebuggingMove, DebuggingState)) -> m ((State, Symbol), (MoveOr Symbol, State))) -> m [((State, Symbol), (MoveOr Symbol, State))]) -> (((DebuggingState, DebuggingSymbol), (DebuggingMove, DebuggingState)) -> m ((State, Symbol), (MoveOr Symbol, State))) -> m [((State, Symbol), (MoveOr Symbol, State))] forall a b. (a -> b) -> a -> b $ \((DebuggingState state1, DebuggingSymbol symbol1), (DebuggingMove symbolOrMove, DebuggingState state2)) -> do State qf <- IsoMap DebuggingState State states' IsoMap DebuggingState State -> DebuggingState -> m State forall c k v (m :: * -> *). (Indexable c k v, MonadFail m) => c -> k -> m v !? DebuggingState state1 Symbol s <- IsoMap DebuggingSymbol Symbol symbols' IsoMap DebuggingSymbol Symbol -> DebuggingSymbol -> m Symbol forall c k v (m :: * -> *). (Indexable c k v, MonadFail m) => c -> k -> m v !? DebuggingSymbol symbol1 MoveOr Symbol sm <- case DebuggingMove symbolOrMove of DebuggingMove L -> MoveOr Symbol -> m (MoveOr Symbol) forall (m :: * -> *) a. Monad m => a -> m a return (MoveOr Symbol -> m (MoveOr Symbol)) -> MoveOr Symbol -> m (MoveOr Symbol) forall a b. (a -> b) -> a -> b $ Move -> MoveOr Symbol forall s. Move -> MoveOr s M Move toLeft DebuggingMove R -> MoveOr Symbol -> m (MoveOr Symbol) forall (m :: * -> *) a. Monad m => a -> m a return (MoveOr Symbol -> m (MoveOr Symbol)) -> MoveOr Symbol -> m (MoveOr Symbol) forall a b. (a -> b) -> a -> b $ Move -> MoveOr Symbol forall s. Move -> MoveOr s M Move toRight D DebuggingSymbol symbol2 -> Symbol -> MoveOr Symbol forall s. s -> MoveOr s S (Symbol -> MoveOr Symbol) -> m Symbol -> m (MoveOr Symbol) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> IsoMap DebuggingSymbol Symbol symbols' IsoMap DebuggingSymbol Symbol -> DebuggingSymbol -> m Symbol forall c k v (m :: * -> *). (Indexable c k v, MonadFail m) => c -> k -> m v !? DebuggingSymbol symbol2 State qt <- IsoMap DebuggingState State states' IsoMap DebuggingState State -> DebuggingState -> m State forall c k v (m :: * -> *). (Indexable c k v, MonadFail m) => c -> k -> m v !? DebuggingState state2 ((State, Symbol), (MoveOr Symbol, State)) -> m ((State, Symbol), (MoveOr Symbol, State)) forall (m :: * -> *) a. Monad m => a -> m a return ((State qf, Symbol s), (MoveOr Symbol sm, State qt)) TuringMachine -> m TuringMachine forall (m :: * -> *) a. Monad m => a -> m a return (TuringMachine -> m TuringMachine) -> TuringMachine -> m TuringMachine forall a b. (a -> b) -> a -> b $ Level -> TuringMachine -> TuringMachine safeOptimize Level O1 (TuringMachine -> TuringMachine) -> TuringMachine -> TuringMachine forall a b. (a -> b) -> a -> b $ Quadruples -> LabeledStates -> Alphabet -> TuringMachine turingMachine ([((State, Symbol), (MoveOr Symbol, State))] -> Quadruples forall c v. UnsafeListable c v => [v] -> c fromList [((State, Symbol), (MoveOr Symbol, State))] quadruplesList) LabeledStates forall c. Nullable c => c emptyC Alphabet alphabet' getStates :: DebuggingTuringMachine -> IsoMap DebuggingState State getStates :: DebuggingTuringMachine -> IsoMap DebuggingState State getStates (DTM (DQuadruples Map (DebuggingState, DebuggingSymbol) (DebuggingMove, DebuggingState) qdrs)) = let Set DebuggingState dstates :: Set DebuggingState = [DebuggingState] -> Set DebuggingState forall c v. UnsafeListable c v => [v] -> c fromList ([DebuggingState] -> Set DebuggingState) -> [DebuggingState] -> Set DebuggingState forall a b. (a -> b) -> a -> b $ (((DebuggingState, DebuggingSymbol), (DebuggingMove, DebuggingState)) -> [DebuggingState]) -> [((DebuggingState, DebuggingSymbol), (DebuggingMove, DebuggingState))] -> [DebuggingState] forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b] concatMap (\((DebuggingState s1, DebuggingSymbol _), (DebuggingMove _, DebuggingState s2)) -> [DebuggingState s1, DebuggingState s2]) ([((DebuggingState, DebuggingSymbol), (DebuggingMove, DebuggingState))] -> [DebuggingState]) -> [((DebuggingState, DebuggingSymbol), (DebuggingMove, DebuggingState))] -> [DebuggingState] forall a b. (a -> b) -> a -> b $ Map (DebuggingState, DebuggingSymbol) (DebuggingMove, DebuggingState) -> [((DebuggingState, DebuggingSymbol), (DebuggingMove, DebuggingState))] forall c v. Listable c v => c -> [v] toList Map (DebuggingState, DebuggingSymbol) (DebuggingMove, DebuggingState) qdrs dstates' :: Set DebuggingState dstates' = DebuggingState finalDState DebuggingState -> Set DebuggingState -> Set DebuggingState forall c v. Deletable c v => v -> c -> c \> DebuggingState startDState DebuggingState -> Set DebuggingState -> Set DebuggingState forall c v. Deletable c v => v -> c -> c \> Set DebuggingState dstates in [(DebuggingState, State)] -> IsoMap DebuggingState State forall c v. UnsafeListable c v => [v] -> c fromList ([(DebuggingState, State)] -> IsoMap DebuggingState State) -> [(DebuggingState, State)] -> IsoMap DebuggingState State forall a b. (a -> b) -> a -> b $ [DebuggingState] -> [State] -> [(DebuggingState, State)] forall a b. [a] -> [b] -> [(a, b)] zip (DebuggingState finalDState DebuggingState -> [DebuggingState] -> [DebuggingState] forall c v. Insertable c v => v -> c -> c +> DebuggingState startDState DebuggingState -> [DebuggingState] -> [DebuggingState] forall c v. Insertable c v => v -> c -> c +> Set DebuggingState -> [DebuggingState] forall c v. Listable c v => c -> [v] toList Set DebuggingState dstates') [State forall a. Bounded a => a minBound..] getSymbols :: DebuggingTuringMachine -> (Alphabet, IsoMap DebuggingSymbol TuringMachine.Symbol) getSymbols :: DebuggingTuringMachine -> (Alphabet, IsoMap DebuggingSymbol Symbol) getSymbols (DTM (DQuadruples Map (DebuggingState, DebuggingSymbol) (DebuggingMove, DebuggingState) qdrs)) = let blank' :: DebuggingSymbol blank' = String -> DebuggingSymbol DSymbol String "." Set DebuggingSymbol dsymbols :: Set DebuggingSymbol = [DebuggingSymbol] -> Set DebuggingSymbol forall c v. UnsafeListable c v => [v] -> c fromList ([DebuggingSymbol] -> Set DebuggingSymbol) -> [DebuggingSymbol] -> Set DebuggingSymbol forall a b. (a -> b) -> a -> b $ (((DebuggingState, DebuggingSymbol), (DebuggingMove, DebuggingState)) -> [DebuggingSymbol]) -> [((DebuggingState, DebuggingSymbol), (DebuggingMove, DebuggingState))] -> [DebuggingSymbol] forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b] concatMap (\case ((DebuggingState _, DebuggingSymbol s), (D DebuggingSymbol s', DebuggingState _)) -> [DebuggingSymbol s, DebuggingSymbol s'] ((DebuggingState _, DebuggingSymbol s), (DebuggingMove, DebuggingState) _) -> [DebuggingSymbol s]) ([((DebuggingState, DebuggingSymbol), (DebuggingMove, DebuggingState))] -> [DebuggingSymbol]) -> [((DebuggingState, DebuggingSymbol), (DebuggingMove, DebuggingState))] -> [DebuggingSymbol] forall a b. (a -> b) -> a -> b $ Map (DebuggingState, DebuggingSymbol) (DebuggingMove, DebuggingState) -> [((DebuggingState, DebuggingSymbol), (DebuggingMove, DebuggingState))] forall c v. Listable c v => c -> [v] toList Map (DebuggingState, DebuggingSymbol) (DebuggingMove, DebuggingState) qdrs dsymbols' :: Set DebuggingSymbol dsymbols' = DebuggingSymbol blank' DebuggingSymbol -> Set DebuggingSymbol -> Set DebuggingSymbol forall c v. Deletable c v => v -> c -> c \> Set DebuggingSymbol dsymbols in ( [(ShowedSymbol, Symbol)] -> Alphabet forall c v. UnsafeListable c v => [v] -> c fromList ([(ShowedSymbol, Symbol)] -> Alphabet) -> [(ShowedSymbol, Symbol)] -> Alphabet forall a b. (a -> b) -> a -> b $ [ShowedSymbol] -> [Symbol] -> [(ShowedSymbol, Symbol)] forall a b. [a] -> [b] -> [(a, b)] zip (ShowedSymbol blank ShowedSymbol -> [ShowedSymbol] -> [ShowedSymbol] forall a. a -> [a] -> [a] : (String -> ShowedSymbol forall a. Read a => String -> a read (String -> ShowedSymbol) -> (DebuggingSymbol -> String) -> DebuggingSymbol -> ShowedSymbol forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> DebuggingSymbol -> String unDSymbol (DebuggingSymbol -> ShowedSymbol) -> [DebuggingSymbol] -> [ShowedSymbol] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Set DebuggingSymbol -> [DebuggingSymbol] forall c v. Listable c v => c -> [v] toList Set DebuggingSymbol dsymbols')) [Symbol forall a. Bounded a => a minBound..], [(DebuggingSymbol, Symbol)] -> IsoMap DebuggingSymbol Symbol forall c v. UnsafeListable c v => [v] -> c fromList ([(DebuggingSymbol, Symbol)] -> IsoMap DebuggingSymbol Symbol) -> [(DebuggingSymbol, Symbol)] -> IsoMap DebuggingSymbol Symbol forall a b. (a -> b) -> a -> b $ [DebuggingSymbol] -> [Symbol] -> [(DebuggingSymbol, Symbol)] forall a b. [a] -> [b] -> [(a, b)] zip (DebuggingSymbol blank' DebuggingSymbol -> [DebuggingSymbol] -> [DebuggingSymbol] forall a. a -> [a] -> [a] : Set DebuggingSymbol -> [DebuggingSymbol] forall c v. Listable c v => c -> [v] toList Set DebuggingSymbol dsymbols') [Symbol forall a. Bounded a => a minBound..] )