#if __GLASGOW_HASKELL__ < 802 {-# OPTIONS_GHC -Wno-redundant-constraints #-} #endif module System.Console.Haskeline.Emacs where import System.Console.Haskeline.Command import System.Console.Haskeline.Monads import System.Console.Haskeline.Key import System.Console.Haskeline.Command.Completion import System.Console.Haskeline.Command.History import System.Console.Haskeline.Command.Undo import System.Console.Haskeline.Command.KillRing import System.Console.Haskeline.LineState import System.Console.Haskeline.InputT import Control.Monad.Catch (MonadMask) import Data.Char type InputCmd s t = forall m . (MonadIO m, MonadMask m) => Command (InputCmdT m) s t type InputKeyCmd s t = forall m . (MonadIO m, MonadMask m) => KeyCommand (InputCmdT m) s t emacsCommands :: InputKeyCmd InsertMode (Maybe String) emacsCommands :: KeyCommand (InputCmdT m) InsertMode (Maybe String) emacsCommands = [KeyCommand (InputCmdT m) InsertMode (Maybe String)] -> KeyCommand (InputCmdT m) InsertMode (Maybe String) forall a. [KeyMap a] -> KeyMap a choiceCmd [ [KeyMap (Command (InputCmdT m) InsertMode InsertMode)] -> KeyMap (Command (InputCmdT m) InsertMode InsertMode) forall a. [KeyMap a] -> KeyMap a choiceCmd [KeyMap (Command (InputCmdT m) InsertMode InsertMode) InputKeyCmd InsertMode InsertMode Evidence bound by a type signature of the constraint type MonadMask m Evidence bound by a type signature of the constraint type MonadIO m simpleActions, KeyMap (Command (InputCmdT m) InsertMode InsertMode) InputKeyCmd InsertMode InsertMode Evidence bound by a type signature of the constraint type MonadMask m Evidence bound by a type signature of the constraint type MonadIO m controlActions] KeyMap (Command (InputCmdT m) InsertMode InsertMode) -> Command (InputCmdT m) InsertMode (Maybe String) -> KeyCommand (InputCmdT m) InsertMode (Maybe String) forall (m :: * -> *) s t u. Monad m => KeyCommand m s t -> Command m t u -> KeyCommand m s u External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m >+> KeyCommand (InputCmdT m) InsertMode (Maybe String) -> Command (InputCmdT m) InsertMode (Maybe String) forall (m :: * -> *) s t. KeyCommand m s t -> Command m s t keyCommand KeyCommand (InputCmdT m) InsertMode (Maybe String) InputKeyCmd InsertMode (Maybe String) Evidence bound by a type signature of the constraint type MonadMask m Evidence bound by a type signature of the constraint type MonadIO m emacsCommands , KeyCommand (InputCmdT m) InsertMode (Maybe String) InputKeyCmd InsertMode (Maybe String) Evidence bound by a type signature of the constraint type MonadMask m Evidence bound by a type signature of the constraint type MonadIO m enders] enders :: InputKeyCmd InsertMode (Maybe String) enders :: KeyCommand (InputCmdT m) InsertMode (Maybe String) enders = [KeyCommand (InputCmdT m) InsertMode (Maybe String)] -> KeyCommand (InputCmdT m) InsertMode (Maybe String) forall a. [KeyMap a] -> KeyMap a choiceCmd [Char -> Key simpleChar Char '\n' Key -> Command (InputCmdT m) InsertMode (Maybe String) -> KeyCommand (InputCmdT m) InsertMode (Maybe String) forall a. Key -> a -> KeyMap a +> Command (InputCmdT m) InsertMode (Maybe String) forall (m :: * -> *) s. (Monad m, Result s) => Command m s (Maybe String) External instance of the constraint type Result InsertMode External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m finish, Key eotKey Key -> Command (InputCmdT m) InsertMode (Maybe String) -> KeyCommand (InputCmdT m) InsertMode (Maybe String) forall a. Key -> a -> KeyMap a +> Command (InputCmdT m) InsertMode (Maybe String) deleteCharOrEOF] where eotKey :: Key eotKey = Char -> Key ctrlChar Char 'd' deleteCharOrEOF :: Command (InputCmdT m) InsertMode (Maybe String) deleteCharOrEOF InsertMode s | InsertMode s InsertMode -> InsertMode -> Bool forall a. Eq a => a -> a -> Bool External instance of the constraint type Eq InsertMode == InsertMode emptyIM = Maybe String -> CmdM (InputCmdT m) (Maybe String) forall (m :: * -> *) a. Monad m => a -> m a External instance of the constraint type forall (m :: * -> *). Monad m => Monad (CmdM m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m return Maybe String forall a. Maybe a Nothing | Bool otherwise = (InsertMode -> InsertMode) -> Command (InputCmdT m) InsertMode InsertMode forall t (m :: * -> *) s. (LineState t, Monad m) => (s -> t) -> Command m s t External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type LineState InsertMode change InsertMode -> InsertMode deleteNext InsertMode s CmdM (InputCmdT m) InsertMode -> Command (InputCmdT m) InsertMode (Maybe String) -> CmdM (InputCmdT m) (Maybe String) forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b External instance of the constraint type forall (m :: * -> *). Monad m => Monad (CmdM m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m >>= Command (InputCmdT m) InsertMode (Maybe String) justDelete justDelete :: Command (InputCmdT m) InsertMode (Maybe String) justDelete = [KeyCommand (InputCmdT m) InsertMode (Maybe String)] -> Command (InputCmdT m) InsertMode (Maybe String) forall (m :: * -> *) s t. [KeyCommand m s t] -> Command m s t keyChoiceCmd [Key eotKey Key -> Command (InputCmdT m) InsertMode (Maybe String) -> KeyCommand (InputCmdT m) InsertMode (Maybe String) forall a. Key -> a -> KeyMap a +> (InsertMode -> InsertMode) -> Command (InputCmdT m) InsertMode InsertMode forall t (m :: * -> *) s. (LineState t, Monad m) => (s -> t) -> Command m s t External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type LineState InsertMode change InsertMode -> InsertMode deleteNext Command (InputCmdT m) InsertMode InsertMode -> Command (InputCmdT m) InsertMode (Maybe String) -> Command (InputCmdT m) InsertMode (Maybe String) forall (m :: * -> *) s t u. Monad m => Command m s t -> Command m t u -> Command m s u External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m >|> Command (InputCmdT m) InsertMode (Maybe String) justDelete , KeyCommand (InputCmdT m) InsertMode (Maybe String) InputKeyCmd InsertMode (Maybe String) Evidence bound by a type signature of the constraint type MonadMask m Evidence bound by a type signature of the constraint type MonadIO m emacsCommands] simpleActions, controlActions :: InputKeyCmd InsertMode InsertMode simpleActions :: KeyCommand (InputCmdT m) InsertMode InsertMode simpleActions = [KeyCommand (InputCmdT m) InsertMode InsertMode] -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. [KeyMap a] -> KeyMap a choiceCmd [ BaseKey -> Key simpleKey BaseKey LeftKey Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> (InsertMode -> InsertMode) -> Command (InputCmdT m) InsertMode InsertMode forall t (m :: * -> *) s. (LineState t, Monad m) => (s -> t) -> Command m s t External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type LineState InsertMode change InsertMode -> InsertMode forall s. Move s => s -> s External instance of the constraint type Move InsertMode goLeft , BaseKey -> Key simpleKey BaseKey RightKey Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> (InsertMode -> InsertMode) -> Command (InputCmdT m) InsertMode InsertMode forall t (m :: * -> *) s. (LineState t, Monad m) => (s -> t) -> Command m s t External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type LineState InsertMode change InsertMode -> InsertMode forall s. Move s => s -> s External instance of the constraint type Move InsertMode goRight , BaseKey -> Key simpleKey BaseKey Backspace Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> (InsertMode -> InsertMode) -> Command (InputCmdT m) InsertMode InsertMode forall t (m :: * -> *) s. (LineState t, Monad m) => (s -> t) -> Command m s t External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type LineState InsertMode change InsertMode -> InsertMode deletePrev , BaseKey -> Key simpleKey BaseKey Delete Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> (InsertMode -> InsertMode) -> Command (InputCmdT m) InsertMode InsertMode forall t (m :: * -> *) s. (LineState t, Monad m) => (s -> t) -> Command m s t External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type LineState InsertMode change InsertMode -> InsertMode deleteNext , (Char -> InsertMode -> InsertMode) -> KeyCommand (InputCmdT m) InsertMode InsertMode forall t (m :: * -> *) s. (LineState t, Monad m) => (Char -> s -> t) -> KeyCommand m s t External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type LineState InsertMode changeFromChar Char -> InsertMode -> InsertMode insertChar , Key -> KeyCommand (InputCmdT m) InsertMode InsertMode forall (m :: * -> *). (MonadState Undo m, CommandMonad m) => Key -> KeyCommand m InsertMode InsertMode External instance of the constraint type forall (m :: * -> *). (MonadIO m, MonadMask m) => CommandMonad (InputCmdT m) Evidence bound by a type signature of the constraint type MonadIO m Evidence bound by a type signature of the constraint type MonadMask m External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall (m :: * -> *) s. Monad m => MonadState s (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m completionCmd (Char -> Key simpleChar Char '\t') , BaseKey -> Key simpleKey BaseKey UpKey Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> Command (InputCmdT m) InsertMode InsertMode forall s (m :: * -> *). (Save s, MonadState HistLog m) => Command m s s External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall (m :: * -> *) s. Monad m => MonadState s (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type Save InsertMode historyBack , BaseKey -> Key simpleKey BaseKey DownKey Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> Command (InputCmdT m) InsertMode InsertMode forall s (m :: * -> *). (Save s, MonadState HistLog m) => Command m s s External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall (m :: * -> *) s. Monad m => MonadState s (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type Save InsertMode historyForward , BaseKey -> Key simpleKey BaseKey SearchReverse Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> Direction -> Command (InputCmdT m) InsertMode InsertMode forall (m :: * -> *). MonadState HistLog m => Direction -> Command m InsertMode InsertMode External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall (m :: * -> *) s. Monad m => MonadState s (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m searchForPrefix Direction Reverse , BaseKey -> Key simpleKey BaseKey SearchForward Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> Direction -> Command (InputCmdT m) InsertMode InsertMode forall (m :: * -> *). MonadState HistLog m => Direction -> Command m InsertMode InsertMode External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall (m :: * -> *) s. Monad m => MonadState s (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m searchForPrefix Direction Forward , KeyCommand (InputCmdT m) InsertMode InsertMode forall (m :: * -> *). MonadState HistLog m => KeyCommand m InsertMode InsertMode External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall (m :: * -> *) s. Monad m => MonadState s (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m searchHistory ] controlActions :: KeyCommand (InputCmdT m) InsertMode InsertMode controlActions = [KeyCommand (InputCmdT m) InsertMode InsertMode] -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. [KeyMap a] -> KeyMap a choiceCmd [ Char -> Key ctrlChar Char 'a' Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> (InsertMode -> InsertMode) -> Command (InputCmdT m) InsertMode InsertMode forall t (m :: * -> *) s. (LineState t, Monad m) => (s -> t) -> Command m s t External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type LineState InsertMode change InsertMode -> InsertMode forall s. Move s => s -> s External instance of the constraint type Move InsertMode moveToStart , Char -> Key ctrlChar Char 'e' Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> (InsertMode -> InsertMode) -> Command (InputCmdT m) InsertMode InsertMode forall t (m :: * -> *) s. (LineState t, Monad m) => (s -> t) -> Command m s t External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type LineState InsertMode change InsertMode -> InsertMode forall s. Move s => s -> s External instance of the constraint type Move InsertMode moveToEnd , Char -> Key ctrlChar Char 'b' Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> (InsertMode -> InsertMode) -> Command (InputCmdT m) InsertMode InsertMode forall t (m :: * -> *) s. (LineState t, Monad m) => (s -> t) -> Command m s t External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type LineState InsertMode change InsertMode -> InsertMode forall s. Move s => s -> s External instance of the constraint type Move InsertMode goLeft , Char -> Key ctrlChar Char 'f' Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> (InsertMode -> InsertMode) -> Command (InputCmdT m) InsertMode InsertMode forall t (m :: * -> *) s. (LineState t, Monad m) => (s -> t) -> Command m s t External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type LineState InsertMode change InsertMode -> InsertMode forall s. Move s => s -> s External instance of the constraint type Move InsertMode goRight , Char -> Key ctrlChar Char 'l' Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> Command (InputCmdT m) InsertMode InsertMode forall (m :: * -> *) s. Command m s s clearScreenCmd , Char -> Key metaChar Char 'f' Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> (InsertMode -> InsertMode) -> Command (InputCmdT m) InsertMode InsertMode forall t (m :: * -> *) s. (LineState t, Monad m) => (s -> t) -> Command m s t External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type LineState InsertMode change InsertMode -> InsertMode wordRight , Char -> Key metaChar Char 'b' Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> (InsertMode -> InsertMode) -> Command (InputCmdT m) InsertMode InsertMode forall t (m :: * -> *) s. (LineState t, Monad m) => (s -> t) -> Command m s t External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type LineState InsertMode change InsertMode -> InsertMode wordLeft , Key -> Key ctrlKey (BaseKey -> Key simpleKey BaseKey LeftKey) Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> (InsertMode -> InsertMode) -> Command (InputCmdT m) InsertMode InsertMode forall t (m :: * -> *) s. (LineState t, Monad m) => (s -> t) -> Command m s t External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type LineState InsertMode change InsertMode -> InsertMode wordLeft , Key -> Key ctrlKey (BaseKey -> Key simpleKey BaseKey RightKey) Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> (InsertMode -> InsertMode) -> Command (InputCmdT m) InsertMode InsertMode forall t (m :: * -> *) s. (LineState t, Monad m) => (s -> t) -> Command m s t External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type LineState InsertMode change InsertMode -> InsertMode wordRight , Char -> Key metaChar Char 'c' Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> (InsertMode -> InsertMode) -> Command (InputCmdT m) InsertMode InsertMode forall t (m :: * -> *) s. (LineState t, Monad m) => (s -> t) -> Command m s t External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type LineState InsertMode change (([Grapheme] -> [Grapheme]) -> InsertMode -> InsertMode modifyWord [Grapheme] -> [Grapheme] capitalize) , Char -> Key metaChar Char 'l' Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> (InsertMode -> InsertMode) -> Command (InputCmdT m) InsertMode InsertMode forall t (m :: * -> *) s. (LineState t, Monad m) => (s -> t) -> Command m s t External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type LineState InsertMode change (([Grapheme] -> [Grapheme]) -> InsertMode -> InsertMode modifyWord ((Char -> Char) -> [Grapheme] -> [Grapheme] mapBaseChars Char -> Char toLower)) , Char -> Key metaChar Char 'u' Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> (InsertMode -> InsertMode) -> Command (InputCmdT m) InsertMode InsertMode forall t (m :: * -> *) s. (LineState t, Monad m) => (s -> t) -> Command m s t External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type LineState InsertMode change (([Grapheme] -> [Grapheme]) -> InsertMode -> InsertMode modifyWord ((Char -> Char) -> [Grapheme] -> [Grapheme] mapBaseChars Char -> Char toUpper)) , Char -> Key ctrlChar Char '_' Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> Command (InputCmdT m) InsertMode InsertMode forall (m :: * -> *) s. (MonadState Undo m, Save s) => Command m s s External instance of the constraint type Save InsertMode External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall (m :: * -> *) s. Monad m => MonadState s (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m commandUndo , Char -> Key ctrlChar Char 'x' Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> KeyCommand (InputCmdT m) InsertMode InsertMode -> Command (InputCmdT m) InsertMode InsertMode forall (m :: * -> *) s. Monad m => KeyCommand m s s -> Command m s s External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m try (Char -> Key ctrlChar Char 'u' Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> Command (InputCmdT m) InsertMode InsertMode forall (m :: * -> *) s. (MonadState Undo m, Save s) => Command m s s External instance of the constraint type Save InsertMode External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall (m :: * -> *) s. Monad m => MonadState s (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m commandUndo) , Char -> Key ctrlChar Char 't' Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> (InsertMode -> InsertMode) -> Command (InputCmdT m) InsertMode InsertMode forall t (m :: * -> *) s. (LineState t, Monad m) => (s -> t) -> Command m s t External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type LineState InsertMode change InsertMode -> InsertMode transposeChars , Char -> Key ctrlChar Char 'p' Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> Command (InputCmdT m) InsertMode InsertMode forall s (m :: * -> *). (Save s, MonadState HistLog m) => Command m s s External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall (m :: * -> *) s. Monad m => MonadState s (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type Save InsertMode historyBack , Char -> Key ctrlChar Char 'n' Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> Command (InputCmdT m) InsertMode InsertMode forall s (m :: * -> *). (Save s, MonadState HistLog m) => Command m s s External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall (m :: * -> *) s. Monad m => MonadState s (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type Save InsertMode historyForward , Char -> Key metaChar Char '<' Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> Command (InputCmdT m) InsertMode InsertMode forall s (m :: * -> *). (Save s, MonadState HistLog m) => Command m s s External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall (m :: * -> *) s. Monad m => MonadState s (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type Save InsertMode historyStart , Char -> Key metaChar Char '>' Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> Command (InputCmdT m) InsertMode InsertMode forall s (m :: * -> *). (Save s, MonadState HistLog m) => Command m s s External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall (m :: * -> *) s. Monad m => MonadState s (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type Save InsertMode historyEnd , BaseKey -> Key simpleKey BaseKey Home Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> (InsertMode -> InsertMode) -> Command (InputCmdT m) InsertMode InsertMode forall t (m :: * -> *) s. (LineState t, Monad m) => (s -> t) -> Command m s t External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type LineState InsertMode change InsertMode -> InsertMode forall s. Move s => s -> s External instance of the constraint type Move InsertMode moveToStart , BaseKey -> Key simpleKey BaseKey End Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> (InsertMode -> InsertMode) -> Command (InputCmdT m) InsertMode InsertMode forall t (m :: * -> *) s. (LineState t, Monad m) => (s -> t) -> Command m s t External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type LineState InsertMode change InsertMode -> InsertMode forall s. Move s => s -> s External instance of the constraint type Move InsertMode moveToEnd , [KeyCommand (InputCmdT m) InsertMode InsertMode] -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. [KeyMap a] -> KeyMap a choiceCmd [ Char -> Key ctrlChar Char 'w' Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> KillHelper -> Command (InputCmdT m) InsertMode InsertMode forall (m :: * -> *) s t. (MonadState KillRing m, MonadState Undo m, Save s, Save t) => KillHelper -> Command m s t External instance of the constraint type Save InsertMode External instance of the constraint type Save InsertMode External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall (m :: * -> *) s. Monad m => MonadState s (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall (m :: * -> *) s. MonadIO m => MonadState s (ReaderT (IORef s) m) External instance of the constraint type forall (m :: * -> *) r. MonadIO m => MonadIO (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. MonadIO m => MonadIO (ReaderT r m) Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m killFromHelper ((InsertMode -> InsertMode) -> KillHelper SimpleMove InsertMode -> InsertMode bigWordLeft) , Key -> Key metaKey (BaseKey -> Key simpleKey BaseKey Backspace) Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> KillHelper -> Command (InputCmdT m) InsertMode InsertMode forall (m :: * -> *) s t. (MonadState KillRing m, MonadState Undo m, Save s, Save t) => KillHelper -> Command m s t External instance of the constraint type Save InsertMode External instance of the constraint type Save InsertMode External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall (m :: * -> *) s. Monad m => MonadState s (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall (m :: * -> *) s. MonadIO m => MonadState s (ReaderT (IORef s) m) External instance of the constraint type forall (m :: * -> *) r. MonadIO m => MonadIO (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. MonadIO m => MonadIO (ReaderT r m) Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m killFromHelper ((InsertMode -> InsertMode) -> KillHelper SimpleMove InsertMode -> InsertMode wordLeft) , Char -> Key metaChar Char 'd' Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> KillHelper -> Command (InputCmdT m) InsertMode InsertMode forall (m :: * -> *) s t. (MonadState KillRing m, MonadState Undo m, Save s, Save t) => KillHelper -> Command m s t External instance of the constraint type Save InsertMode External instance of the constraint type Save InsertMode External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall (m :: * -> *) s. Monad m => MonadState s (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall (m :: * -> *) s. MonadIO m => MonadState s (ReaderT (IORef s) m) External instance of the constraint type forall (m :: * -> *) r. MonadIO m => MonadIO (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. MonadIO m => MonadIO (ReaderT r m) Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m killFromHelper ((InsertMode -> InsertMode) -> KillHelper SimpleMove InsertMode -> InsertMode wordRight) , Char -> Key ctrlChar Char 'k' Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> KillHelper -> Command (InputCmdT m) InsertMode InsertMode forall (m :: * -> *) s t. (MonadState KillRing m, MonadState Undo m, Save s, Save t) => KillHelper -> Command m s t External instance of the constraint type Save InsertMode External instance of the constraint type Save InsertMode External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall (m :: * -> *) s. Monad m => MonadState s (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall (m :: * -> *) s. MonadIO m => MonadState s (ReaderT (IORef s) m) External instance of the constraint type forall (m :: * -> *) r. MonadIO m => MonadIO (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. MonadIO m => MonadIO (ReaderT r m) Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m killFromHelper ((InsertMode -> InsertMode) -> KillHelper SimpleMove InsertMode -> InsertMode forall s. Move s => s -> s External instance of the constraint type Move InsertMode moveToEnd) , BaseKey -> Key simpleKey BaseKey KillLine Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> KillHelper -> Command (InputCmdT m) InsertMode InsertMode forall (m :: * -> *) s t. (MonadState KillRing m, MonadState Undo m, Save s, Save t) => KillHelper -> Command m s t External instance of the constraint type Save InsertMode External instance of the constraint type Save InsertMode External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall (m :: * -> *) s. Monad m => MonadState s (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall (m :: * -> *) s. MonadIO m => MonadState s (ReaderT (IORef s) m) External instance of the constraint type forall (m :: * -> *) r. MonadIO m => MonadIO (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. MonadIO m => MonadIO (ReaderT r m) Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m killFromHelper ((InsertMode -> InsertMode) -> KillHelper SimpleMove InsertMode -> InsertMode forall s. Move s => s -> s External instance of the constraint type Move InsertMode moveToStart) ] , Char -> Key ctrlChar Char 'y' Key -> Command (InputCmdT m) InsertMode InsertMode -> KeyCommand (InputCmdT m) InsertMode InsertMode forall a. Key -> a -> KeyMap a +> Command (InputCmdT m) InsertMode InsertMode InputCmd InsertMode InsertMode Evidence bound by a type signature of the constraint type MonadMask m Evidence bound by a type signature of the constraint type MonadIO m rotatePaste ] rotatePaste :: InputCmd InsertMode InsertMode rotatePaste :: Command (InputCmdT m) InsertMode InsertMode rotatePaste InsertMode im = CmdM (InputCmdT m) KillRing forall s (m :: * -> *). MonadState s m => m s External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall s (m :: * -> *) (t :: (* -> *) -> * -> *). (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) External instance of the constraint type forall (m :: * -> *) s. MonadIO m => MonadState s (ReaderT (IORef s) m) External instance of the constraint type forall (m :: * -> *) r. MonadIO m => MonadIO (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. MonadIO m => MonadIO (ReaderT r m) Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type forall s. MonadTrans (StateT s) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m External instance of the constraint type MonadTrans CmdM External instance of the constraint type forall (m :: * -> *). Monad m => Monad (CmdM m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m get CmdM (InputCmdT m) KillRing -> (KillRing -> CmdM (InputCmdT m) InsertMode) -> CmdM (InputCmdT m) InsertMode forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b External instance of the constraint type forall (m :: * -> *). Monad m => Monad (CmdM m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m >>= KillRing -> CmdM (InputCmdT m) InsertMode forall {m :: * -> *}. Monad m => KillRing -> CmdM m InsertMode External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) s. Monad m => Monad (StateT s m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *) r. Monad m => Monad (ReaderT r m) External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m Evidence bound by a type signature of the constraint type MonadIO m loop where loop :: KillRing -> CmdM m InsertMode loop KillRing kr = case KillRing -> Maybe [Grapheme] forall a. Stack a -> Maybe a peek KillRing kr of Maybe [Grapheme] Nothing -> InsertMode -> CmdM m InsertMode forall (m :: * -> *) a. Monad m => a -> m a External instance of the constraint type forall (m :: * -> *). Monad m => Monad (CmdM m) Evidence bound by a type signature of the constraint type Monad m return InsertMode im Just [Grapheme] s -> InsertMode -> CmdM m InsertMode forall (m :: * -> *) s. (Monad m, LineState s) => Command m s s External instance of the constraint type LineState InsertMode Evidence bound by a type signature of the constraint type Monad m setState ([Grapheme] -> InsertMode -> InsertMode insertGraphemes [Grapheme] s InsertMode im) CmdM m InsertMode -> (InsertMode -> CmdM m InsertMode) -> CmdM m InsertMode forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b External instance of the constraint type forall (m :: * -> *). Monad m => Monad (CmdM m) Evidence bound by a type signature of the constraint type Monad m >>= KeyCommand m InsertMode InsertMode -> InsertMode -> CmdM m InsertMode forall (m :: * -> *) s. Monad m => KeyCommand m s s -> Command m s s Evidence bound by a type signature of the constraint type Monad m try (Char -> Key metaChar Char 'y' Key -> (InsertMode -> CmdM m InsertMode) -> KeyCommand m InsertMode InsertMode forall a. Key -> a -> KeyMap a +> \InsertMode _ -> KillRing -> CmdM m InsertMode loop (KillRing -> KillRing forall a. Stack a -> Stack a rotate KillRing kr)) wordRight, wordLeft, bigWordLeft :: InsertMode -> InsertMode wordRight :: InsertMode -> InsertMode wordRight = (InsertMode -> Bool) -> InsertMode -> InsertMode goRightUntil ((Char -> Bool) -> InsertMode -> Bool atStart (Bool -> Bool not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool forall b c a. (b -> c) -> (a -> b) -> a -> c . Char -> Bool isAlphaNum)) wordLeft :: InsertMode -> InsertMode wordLeft = (InsertMode -> Bool) -> InsertMode -> InsertMode goLeftUntil ((Char -> Bool) -> InsertMode -> Bool atStart Char -> Bool isAlphaNum) bigWordLeft :: InsertMode -> InsertMode bigWordLeft = (InsertMode -> Bool) -> InsertMode -> InsertMode goLeftUntil ((Char -> Bool) -> InsertMode -> Bool atStart (Bool -> Bool not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool forall b c a. (b -> c) -> (a -> b) -> a -> c . Char -> Bool isSpace)) modifyWord :: ([Grapheme] -> [Grapheme]) -> InsertMode -> InsertMode modifyWord :: ([Grapheme] -> [Grapheme]) -> InsertMode -> InsertMode modifyWord [Grapheme] -> [Grapheme] f InsertMode im = [Grapheme] -> [Grapheme] -> InsertMode IMode ([Grapheme] -> [Grapheme] forall a. [a] -> [a] reverse ([Grapheme] -> [Grapheme] f [Grapheme] ys1) [Grapheme] -> [Grapheme] -> [Grapheme] forall a. [a] -> [a] -> [a] ++ [Grapheme] xs) [Grapheme] ys2 where IMode [Grapheme] xs [Grapheme] ys = (Char -> Bool) -> InsertMode -> InsertMode skipRight (Bool -> Bool not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool forall b c a. (b -> c) -> (a -> b) -> a -> c . Char -> Bool isAlphaNum) InsertMode im ([Grapheme] ys1,[Grapheme] ys2) = (Grapheme -> Bool) -> [Grapheme] -> ([Grapheme], [Grapheme]) forall a. (a -> Bool) -> [a] -> ([a], [a]) span (Char -> Bool isAlphaNum (Char -> Bool) -> (Grapheme -> Char) -> Grapheme -> Bool forall b c a. (b -> c) -> (a -> b) -> a -> c . Grapheme -> Char baseChar) [Grapheme] ys capitalize :: [Grapheme] -> [Grapheme] capitalize :: [Grapheme] -> [Grapheme] capitalize [] = [] capitalize (Grapheme c:[Grapheme] cs) = (Char -> Char) -> Grapheme -> Grapheme modifyBaseChar Char -> Char toUpper Grapheme c Grapheme -> [Grapheme] -> [Grapheme] forall a. a -> [a] -> [a] : [Grapheme] cs