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

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


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

import           Control.Monad                    (void)
import qualified Data.Text                        as T (append, pack)
import qualified Data.Attoparsec.Text             as P (anyChar, many1, option, space, string, try)
import           Yi.Command.Help                  (displayHelpFor)
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, cmdShow))

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
"help"
    Text
cmd <- Text -> Parser Text Text -> Parser Text Text
forall (f :: * -> *) a. Alternative f => a -> f a -> f a
P.option Text
"" (Parser Text Text -> Parser Text Text)
-> Parser Text Text -> Parser Text 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 (Parser Text Text -> Parser Text Text)
-> Parser Text Text -> Parser Text Text
forall a b. (a -> b) -> a -> 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
      [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 (f :: * -> *) a. Alternative f => f a -> f [a]
P.many1 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
$! ExCommand
Common.impureExCommand {
        cmdAction :: Action
cmdAction   = YiM () -> Action
forall a. Show a => YiM a -> Action
YiA (YiM () -> Action) -> YiM () -> Action
forall a b. (a -> b) -> a -> b
$ Text -> YiM ()
displayHelpFor Text
cmd
      , cmdShow :: Text
cmdShow     = Text
"help" Text -> Text -> Text
`T.append`
                      if Text
cmd Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
""
                         then Text
""
                         else Text
" " Text -> Text -> Text
`T.append` Text
cmd
      }