{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_HADDOCK show-extensions #-}
module Yi.Keymap.Vim.Ex.Commands.Edit (parse) where
import Control.Applicative (Alternative ((<|>)))
import Control.Monad (void, when)
import Data.Maybe (isJust)
import qualified Data.Text as T (Text, append, pack, unpack, null)
import qualified Data.Attoparsec.Text as P (anyChar, many', many1, space, string, try, option)
import Yi.Editor (MonadEditor (withEditor), newTabE)
import Yi.File (openNewFile)
import Yi.Keymap (Action (YiA))
import Yi.Keymap.Vim.Common (EventString)
import qualified Yi.Keymap.Vim.Ex.Commands.Common as Common (filenameComplete, impureExCommand, parse)
import Yi.Keymap.Vim.Ex.Types (ExCommand (cmdAction, cmdComplete, cmdShow))
import Yi.Editor (printMsg)
parse :: EventString -> Maybe ExCommand
parse :: EventString -> Maybe ExCommand
parse = Parser ExCommand -> EventString -> Maybe ExCommand
Common.parse (Parser ExCommand -> EventString -> Maybe ExCommand)
-> Parser ExCommand -> EventString -> Maybe ExCommand
forall a b. (a -> b) -> a -> b
$ do
Maybe Text
tab <- Maybe Text -> Parser Text (Maybe Text) -> Parser Text (Maybe Text)
forall (f :: * -> *) a. Alternative f => a -> f a -> f a
P.option Maybe Text
forall a. Maybe a
Nothing (Parser Text (Maybe Text) -> Parser Text (Maybe Text))
-> Parser Text (Maybe Text) -> Parser Text (Maybe Text)
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text)
-> Parser Text Text -> Parser Text (Maybe Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Parser Text Text
P.string Text
"tab"
Parser Text Text -> Parser Text ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Parser Text Text -> Parser Text ())
-> Parser Text Text -> Parser Text ()
forall a b. (a -> b) -> a -> b
$ Parser Text Text -> Parser Text Text
forall i a. Parser i a -> Parser i a
P.try (Text -> Parser Text Text
P.string Text
"edit") Parser Text Text -> Parser Text Text -> Parser Text Text
forall a. Parser Text a -> Parser Text a -> Parser Text a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> Parser Text Text
P.string Text
"e"
Parser Text [Char] -> Parser Text ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Parser Text [Char] -> Parser Text ())
-> Parser Text [Char] -> Parser Text ()
forall a b. (a -> b) -> a -> b
$ Parser Text Char -> Parser Text [Char]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
P.many1 Parser Text Char
P.space
Text
filename <- [Char] -> Text
T.pack ([Char] -> Text) -> Parser Text [Char] -> Parser Text Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Text Char -> Parser Text [Char]
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
P.many' Parser Text Char
P.anyChar
ExCommand -> Parser ExCommand
forall a. a -> Parser Text a
forall (m :: * -> *) a. Monad m => a -> m a
return (ExCommand -> Parser ExCommand) -> ExCommand -> Parser ExCommand
forall a b. (a -> b) -> a -> b
$! Bool -> Text -> ExCommand
edit (Maybe Text -> Bool
forall a. Maybe a -> Bool
isJust Maybe Text
tab) Text
filename
edit :: Bool -> T.Text -> ExCommand
edit :: Bool -> Text -> ExCommand
edit Bool
tab Text
f = ExCommand
Common.impureExCommand {
cmdShow = showEdit tab f
, cmdAction = YiA $
if T.null f
then printMsg "No file name"
else do
when tab $ withEditor newTabE
openNewFile $ T.unpack f
, cmdComplete = (fmap . fmap)
(showEdit tab) (Common.filenameComplete f)
}
showEdit :: Bool -> T.Text -> T.Text
showEdit :: Bool -> Text -> Text
showEdit Bool
tab Text
f = (if Bool
tab then Text
"tab" else Text
"") Text -> Text -> Text
`T.append` Text
"edit " Text -> Text -> Text
`T.append` Text
f