module Client.Commands.WordCompletion
( Prefix(..)
, wordComplete
, WordCompletionMode(..)
, plainWordCompleteMode
, defaultNickWordCompleteMode
, slackNickWordCompleteMode
) where
import qualified Client.State.EditBox as Edit
import Control.Applicative
import Control.Lens
import Control.Monad
import Data.List
import qualified Data.Set as Set
import Data.String (IsString(..))
import qualified Data.Text as Text
import Data.Text (Text)
import Irc.Identifier
data WordCompletionMode = WordCompletionMode
{ wcmStartPrefix, wcmStartSuffix, wcmMiddlePrefix, wcmMiddleSuffix :: String }
deriving Show
plainWordCompleteMode :: WordCompletionMode
plainWordCompleteMode = WordCompletionMode "" "" "" ""
defaultNickWordCompleteMode :: WordCompletionMode
defaultNickWordCompleteMode = WordCompletionMode "" ": " "" ""
slackNickWordCompleteMode :: WordCompletionMode
slackNickWordCompleteMode = WordCompletionMode "@" " " "@" ""
wordComplete ::
Prefix a =>
WordCompletionMode ->
Bool ->
[a] ->
[a] ->
Edit.EditBox -> Maybe Edit.EditBox
wordComplete mode isReversed hint vals box =
do let current = currentWord mode box
guard (not (null current))
let cur = fromString current
case view Edit.lastOperation box of
Edit.TabOperation patternStr
| isPrefix pat cur ->
do next <- tabSearch isReversed pat cur vals
Just $ replaceWith mode (toString next) box
where
pat = fromString patternStr
_ ->
do next <- find (isPrefix cur) hint <|>
tabSearch isReversed cur cur vals
Just $ set Edit.lastOperation (Edit.TabOperation current)
$ replaceWith mode (toString next) box
replaceWith :: WordCompletionMode -> String -> Edit.EditBox -> Edit.EditBox
replaceWith (WordCompletionMode spfx ssfx mpfx msfx) str box =
let box1 = Edit.killWordBackward False box
str1 | view Edit.pos box1 == 0 = spfx ++ str ++ ssfx
| otherwise = mpfx ++ str ++ msfx
in over Edit.content (Edit.insertString str1) box1
currentWord :: WordCompletionMode -> Edit.EditBox -> String
currentWord (WordCompletionMode spfx ssfx mpfx msfx) box
= dropWhile (`elem`pfx)
$ reverse
$ takeWhile (/= ' ')
$ dropWhile (`elem`sfx)
$ reverse
$ take n txt
where
pfx = spfx++mpfx
sfx = ssfx++msfx
Edit.Line n txt = view Edit.line box
class (IsString a, Ord a) => Prefix a where
isPrefix :: a -> a -> Bool
toString :: a -> String
instance Prefix Identifier where
isPrefix = idPrefix
toString = Text.unpack . idText
instance Prefix Text where
isPrefix = Text.isPrefixOf
toString = Text.unpack
tabSearch ::
Prefix a =>
Bool ->
a ->
a ->
[a] ->
Maybe a
tabSearch isReversed pat cur vals
| Set.null valSet = Nothing
| Just next <- advanceFun cur valSet = Just next
| isReversed = Just $! Set.findMax valSet
| otherwise = Just $! Set.findMin valSet
where
valSet = Set.fromList (filter (isPrefix pat) vals)
advanceFun | isReversed = Set.lookupLT
| otherwise = Set.lookupGT