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

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

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

import           Control.Monad                    (void)
import qualified Data.Attoparsec.Text             as P (match, string)
import           Data.Monoid                      ((<>))
import qualified Data.Text                        as T (Text)
import           Yi.Buffer
import           Yi.Keymap                        (Action (BufferA))
import           Yi.Keymap.Vim.Common             (EventString)
import qualified Yi.Keymap.Vim.Ex.Commands.Common as Common (parse, parseRange, pureExCommand)
import           Yi.Keymap.Vim.Ex.Types           (ExCommand (cmdAction, cmdComplete, 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
    (Text
regionText, Maybe (BufferM Region)
region) <- Parser (Maybe (BufferM Region))
-> Parser (Text, Maybe (BufferM Region))
forall a. Parser a -> Parser (Text, a)
P.match Parser (Maybe (BufferM Region))
Common.parseRange
    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
"sort"
    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 (BufferM Region) -> Text -> ExCommand
sort Maybe (BufferM Region)
region Text
regionText

sort :: Maybe (BufferM Region) -> T.Text -> ExCommand
sort :: Maybe (BufferM Region) -> Text -> ExCommand
sort Maybe (BufferM Region)
r Text
rt = ExCommand
Common.pureExCommand {
    cmdShow :: Text
cmdShow = Text
rt Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"sort"
  , cmdAction :: Action
cmdAction = BufferM () -> Action
forall a. Show a => BufferM a -> Action
BufferA (BufferM () -> Action) -> BufferM () -> Action
forall a b. (a -> b) -> a -> b
$ Maybe (BufferM Region) -> BufferM ()
sortA Maybe (BufferM Region)
r
  , cmdComplete :: YiM [Text]
cmdComplete = [Text] -> YiM [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return [Text
rt Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"sort"]
  }

sortA :: Maybe (BufferM Region) -> BufferM ()
sortA :: Maybe (BufferM Region) -> BufferM ()
sortA Maybe (BufferM Region)
r = do
    Region
region <- case Maybe (BufferM Region)
r of
        Maybe (BufferM Region)
Nothing -> TextUnit -> BufferM Region
regionOfB TextUnit
Document
        Just BufferM Region
r' -> BufferM Region
r'
    Region -> BufferM ()
sortLinesWithRegion Region
region{regionEnd :: Point
regionEnd = Region -> Point
regionEnd Region
region Point -> Point -> Point
forall a. Num a => a -> a -> a
- Point
1}