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

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

module Yi.Keymap.Vim.Ex.Commands.Tag (parse) where

import           Control.Applicative              (Alternative ((<|>)))
import           Control.Monad                    (void)
import qualified Data.Attoparsec.Text             as P (Parser, anyChar, endOfInput,
                                                        many1, option,
                                                        space, string)
import           Data.Monoid                      ((<>))
import qualified Data.Text                        as T (pack)
import           Yi.Keymap                        (Action (YiA))
import           Yi.Keymap.Vim.Common             (EventString)
import qualified Yi.Keymap.Vim.Ex.Commands.Common as Common (impureExCommand, parse)
import           Yi.Keymap.Vim.Ex.Types           (ExCommand (cmdAction, cmdComplete, cmdShow))
import           Yi.Keymap.Vim.Tag                (completeVimTag, gotoTag, nextTag, unpopTag)
import           Yi.Tag                           (Tag (Tag))

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
    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
$ Text -> Parser Text Text
P.string Text
"t"
    Parser ExCommand
parseTag Parser ExCommand -> Parser ExCommand -> Parser ExCommand
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser ExCommand
parseNext

parseTag :: P.Parser ExCommand
parseTag :: Parser ExCommand
parseTag = do
  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
$ Text -> Parser Text Text
P.string Text
"a"
  Parser Text (Maybe Text) -> Parser Text ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Parser Text (Maybe Text) -> Parser Text ())
-> (Parser Text (Maybe Text) -> Parser Text (Maybe Text))
-> Parser Text (Maybe Text)
-> Parser Text ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 ())
-> Parser Text (Maybe Text) -> Parser 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
"g"
  Maybe [Char]
t <- Maybe [Char]
-> Parser Text (Maybe [Char]) -> Parser Text (Maybe [Char])
forall (f :: * -> *) a. Alternative f => a -> f a -> f a
P.option Maybe [Char]
forall a. Maybe a
Nothing (Parser Text (Maybe [Char]) -> Parser Text (Maybe [Char]))
-> Parser Text (Maybe [Char]) -> Parser Text (Maybe [Char])
forall a b. (a -> b) -> a -> b
$ [Char] -> Maybe [Char]
forall a. a -> Maybe a
Just ([Char] -> Maybe [Char])
-> Parser Text [Char] -> Parser Text (Maybe [Char])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> do
      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
      Parser Text Char -> Parser Text [Char]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
P.many1 Parser Text Char
P.anyChar
  case Maybe [Char]
t of
    Maybe [Char]
Nothing -> Parser Text ()
forall t. Chunk t => Parser t ()
P.endOfInput Parser Text () -> Parser ExCommand -> Parser ExCommand
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ExCommand -> Parser ExCommand
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Tag -> ExCommand
tag Maybe Tag
forall a. Maybe a
Nothing)
    Just [Char]
t' -> 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
$! Maybe Tag -> ExCommand
tag (Tag -> Maybe Tag
forall a. a -> Maybe a
Just (Text -> Tag
Tag ([Char] -> Text
T.pack [Char]
t')))

parseNext :: P.Parser ExCommand
parseNext :: Parser ExCommand
parseNext = do
  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
$ Text -> Parser Text Text
P.string Text
"next"
  ExCommand -> Parser ExCommand
forall (m :: * -> *) a. Monad m => a -> m a
return ExCommand
next

tag :: Maybe Tag -> ExCommand
tag :: Maybe Tag -> ExCommand
tag Maybe Tag
Nothing = ExCommand
Common.impureExCommand {
    cmdShow :: Text
cmdShow = Text
"tag"
  , cmdAction :: Action
cmdAction = YiM () -> Action
forall a. Show a => YiM a -> Action
YiA YiM ()
unpopTag
  , cmdComplete :: YiM [Text]
cmdComplete = [Text] -> YiM [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return [Text
"tag"]
  }
tag (Just (Tag Text
t)) = ExCommand
Common.impureExCommand {
    cmdShow :: Text
cmdShow = Text
"tag " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
t
  , cmdAction :: Action
cmdAction = YiM () -> Action
forall a. Show a => YiM a -> Action
YiA (YiM () -> Action) -> YiM () -> Action
forall a b. (a -> b) -> a -> b
$ Tag -> Int -> Maybe ([Char], Int, Int) -> YiM ()
gotoTag (Text -> Tag
Tag Text
t) Int
0 Maybe ([Char], Int, Int)
forall a. Maybe a
Nothing
  , cmdComplete :: YiM [Text]
cmdComplete = (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Text
"tag " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>) ([Text] -> [Text]) -> YiM [Text] -> YiM [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> YiM [Text]
completeVimTag Text
t
  }

next :: ExCommand
next :: ExCommand
next = ExCommand
Common.impureExCommand {
    cmdShow :: Text
cmdShow = Text
"tnext"
  , cmdAction :: Action
cmdAction = YiM () -> Action
forall a. Show a => YiM a -> Action
YiA YiM ()
nextTag
  , cmdComplete :: YiM [Text]
cmdComplete = [Text] -> YiM [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return [Text
"tnext"]
  }