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

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

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

import           Control.Applicative              (Alternative ((<|>)))
import           Data.Attoparsec.Text             as P (choice, Parser)
import           Data.Text                        (Text)
import           Data.Monoid                      ((<>))
import           Yi.Command                       (stackCommandE)
import           Yi.Keymap                        (Action (YiA))
import           Yi.Keymap.Vim.Common             (EventString)
import qualified Yi.Keymap.Vim.Ex.Commands.Common as Common (commandArgs, impureExCommand, parse)
import           Yi.Keymap.Vim.Ex.Types           (ExCommand (cmdAction, cmdShow))
import           Yi.MiniBuffer                    (CommandArguments (CommandArguments))

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
    Text
cmd <- Parser Text Text
"stack" Parser Text Text -> Parser Text Text -> Parser Text Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (Parser Text Text
" " Parser Text Text -> Parser Text Text -> Parser Text Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> [Parser Text Text] -> Parser Text Text
forall (f :: * -> *) a. Alternative f => [f a] -> f a
P.choice [Parser Text Text]
commands Parser Text Text -> Parser Text Text -> Parser Text Text
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> Parser Text Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
"build")
    [Text]
args <- Parser [Text]
Common.commandArgs
    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 {
        cmdShow :: Text
cmdShow = Text
"stack " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
cmd
      , 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 -> CommandArguments -> YiM ()
stackCommandE Text
cmd (CommandArguments -> YiM ()) -> CommandArguments -> YiM ()
forall a b. (a -> b) -> a -> b
$ [Text] -> CommandArguments
CommandArguments [Text]
args
      }

commands :: [P.Parser Text]
commands :: [Parser Text Text]
commands =
  [ Parser Text Text
"build"
  , Parser Text Text
"install"
  , Parser Text Text
"uninstall"
  , Parser Text Text
"test"
  , Parser Text Text
"bench"
  , Parser Text Text
"haddock"
  , Parser Text Text
"new"
  , Parser Text Text
"templates"
  , Parser Text Text
"init"
  , Parser Text Text
"solver"
  , Parser Text Text
"setup"
  , Parser Text Text
"path"
  , Parser Text Text
"unpack"
  , Parser Text Text
"update"
  , Parser Text Text
"upgrade"
  , Parser Text Text
"upload"
  , Parser Text Text
"sdist"
  , Parser Text Text
"dot"
  , Parser Text Text
"exec"
  , Parser Text Text
"ghc"
  , Parser Text Text
"ghci"
  , Parser Text Text
"repl"
  , Parser Text Text
"runghc"
  , Parser Text Text
"runhaskell"
  , Parser Text Text
"eval"
  , Parser Text Text
"clean"
  , Parser Text Text
"list-dependencies"
  , Parser Text Text
"query"
  , Parser Text Text
"ide"
  , Parser Text Text
"docker"
  , Parser Text Text
"config"
  , Parser Text Text
"image"
  , Parser Text Text
"hpc"
  ]