{-# OPTIONS_HADDOCK hide #-}
module Byline.Internal.Completion
( CompletionFunc,
Completion (..),
runCompletionFunction,
runCompletionFunctions,
)
where
import qualified Data.Text as Text
import qualified System.Console.Haskeline.Completion as Haskeline
type CompletionFunc m = (Text, Text) -> m (Text, [Completion])
data Completion = Completion
{
Completion -> Text
replacement :: Text,
Completion -> Text
display :: Text,
Completion -> Bool
isFinished :: Bool
}
deriving (Completion -> Completion -> Bool
(Completion -> Completion -> Bool)
-> (Completion -> Completion -> Bool) -> Eq Completion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Completion -> Completion -> Bool
$c/= :: Completion -> Completion -> Bool
== :: Completion -> Completion -> Bool
$c== :: Completion -> Completion -> Bool
Eq, Eq Completion
Eq Completion
-> (Completion -> Completion -> Ordering)
-> (Completion -> Completion -> Bool)
-> (Completion -> Completion -> Bool)
-> (Completion -> Completion -> Bool)
-> (Completion -> Completion -> Bool)
-> (Completion -> Completion -> Completion)
-> (Completion -> Completion -> Completion)
-> Ord Completion
Completion -> Completion -> Bool
Completion -> Completion -> Ordering
Completion -> Completion -> Completion
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Completion -> Completion -> Completion
$cmin :: Completion -> Completion -> Completion
max :: Completion -> Completion -> Completion
$cmax :: Completion -> Completion -> Completion
>= :: Completion -> Completion -> Bool
$c>= :: Completion -> Completion -> Bool
> :: Completion -> Completion -> Bool
$c> :: Completion -> Completion -> Bool
<= :: Completion -> Completion -> Bool
$c<= :: Completion -> Completion -> Bool
< :: Completion -> Completion -> Bool
$c< :: Completion -> Completion -> Bool
compare :: Completion -> Completion -> Ordering
$ccompare :: Completion -> Completion -> Ordering
$cp1Ord :: Eq Completion
Ord, Int -> Completion -> ShowS
[Completion] -> ShowS
Completion -> String
(Int -> Completion -> ShowS)
-> (Completion -> String)
-> ([Completion] -> ShowS)
-> Show Completion
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Completion] -> ShowS
$cshowList :: [Completion] -> ShowS
show :: Completion -> String
$cshow :: Completion -> String
showsPrec :: Int -> Completion -> ShowS
$cshowsPrec :: Int -> Completion -> ShowS
Show)
convertCompletion :: Completion -> Haskeline.Completion
convertCompletion :: Completion -> Completion
convertCompletion (Completion Text
r Text
d Bool
i) =
Completion :: String -> String -> Bool -> Completion
Haskeline.Completion
{ replacement :: String
Haskeline.replacement = Text -> String
forall a. ToString a => a -> String
toString Text
r,
display :: String
Haskeline.display = Text -> String
forall a. ToString a => a -> String
toString Text
d,
isFinished :: Bool
Haskeline.isFinished = Bool
i
}
runCompletionFunction ::
Monad m =>
CompletionFunc m ->
Haskeline.CompletionFunc m
runCompletionFunction :: CompletionFunc m -> CompletionFunc m
runCompletionFunction CompletionFunc m
comp (String
left, String
right) = do
(Text
output, [Completion]
completions) <-
CompletionFunc m
comp
( Text -> Text
Text.reverse (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ String -> Text
forall a. ToText a => a -> Text
toText String
left,
String -> Text
forall a. ToText a => a -> Text
toText String
right
)
(String, [Completion]) -> m (String, [Completion])
forall (f :: * -> *) a. Applicative f => a -> f a
pure
( Text -> String
forall a. ToString a => a -> String
toString (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ Text -> Text
Text.reverse Text
output,
(Completion -> Completion) -> [Completion] -> [Completion]
forall a b. (a -> b) -> [a] -> [b]
map Completion -> Completion
convertCompletion [Completion]
completions
)
runCompletionFunctions ::
forall m.
Monad m =>
[CompletionFunc m] ->
Haskeline.CompletionFunc m
runCompletionFunctions :: [CompletionFunc m] -> CompletionFunc m
runCompletionFunctions [CompletionFunc m]
fs (String, String)
input =
((String, [Completion])
-> CompletionFunc m -> m (String, [Completion]))
-> (String, [Completion])
-> [CompletionFunc m]
-> m (String, [Completion])
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldlM (String, [Completion])
-> CompletionFunc m -> m (String, [Completion])
go (String
forall a. Monoid a => a
mempty, [Completion]
forall a. Monoid a => a
mempty) [CompletionFunc m]
fs
where
go ::
(String, [Haskeline.Completion]) ->
CompletionFunc m ->
m (String, [Haskeline.Completion])
go :: (String, [Completion])
-> CompletionFunc m -> m (String, [Completion])
go (String, [Completion])
prev CompletionFunc m
f = case (String, [Completion])
prev of
(String
_, []) -> CompletionFunc m -> CompletionFunc m
forall (m :: * -> *).
Monad m =>
CompletionFunc m -> CompletionFunc m
runCompletionFunction CompletionFunc m
f (String, String)
input
(String, [Completion])
_ -> (String, [Completion]) -> m (String, [Completion])
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String, [Completion])
prev