{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_HADDOCK show-extensions #-}

-- |
-- Module      :  Yi.Keymap.Vim.Ex.Commands.Edit
-- License     :  GPL-2
-- Maintainer  :  yi-devel@googlegroups.com
-- Stability   :  experimental
-- Portability :  portable
--
-- Implements quit commands.

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 (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 (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 :: Text
cmdShow = Bool -> Text -> Text
showEdit Bool
tab Text
f
  , cmdAction :: Action
cmdAction = YiM () -> Action
forall a. Show a => YiM a -> Action
YiA (YiM () -> Action) -> YiM () -> Action
forall a b. (a -> b) -> a -> b
$
        if Text -> Bool
T.null Text
f
          then Text -> YiM ()
forall (m :: * -> *). MonadEditor m => Text -> m ()
printMsg Text
"No file name"
          else do
            Bool -> YiM () -> YiM ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
tab (YiM () -> YiM ()) -> YiM () -> YiM ()
forall a b. (a -> b) -> a -> b
$ EditorM () -> YiM ()
forall (m :: * -> *) a. MonadEditor m => EditorM a -> m a
withEditor EditorM ()
newTabE
            [Char] -> YiM ()
openNewFile ([Char] -> YiM ()) -> [Char] -> YiM ()
forall a b. (a -> b) -> a -> b
$ Text -> [Char]
T.unpack Text
f
  , cmdComplete :: YiM [Text]
cmdComplete = (([Text] -> [Text]) -> YiM [Text] -> YiM [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (([Text] -> [Text]) -> YiM [Text] -> YiM [Text])
-> ((Text -> Text) -> [Text] -> [Text])
-> (Text -> Text)
-> YiM [Text]
-> YiM [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Text) -> [Text] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap)
                    (Bool -> Text -> Text
showEdit Bool
tab) (Text -> YiM [Text]
Common.filenameComplete Text
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