{-# Language OverloadedStrings, DeriveFunctor #-}
module Client.Commands.Recognizer
( Recognizer
, recognize
, Recognition(..)
, fromCommands
, addCommand
, keys
) where
import Control.Monad
import Control.Applicative hiding (empty)
import Data.HashMap.Strict (lookup,insertWith,HashMap,empty,unionWith,fromList,toList)
import Data.Text (Text)
import qualified Data.Text as Text
import Data.Maybe
import Prelude hiding (all,lookup)
data Recognizer a
= Branch !Text !(Maybe a) !(HashMap Char (Recognizer a))
deriving (Show, Functor)
instance Monoid (Recognizer a) where
mempty = Branch "" Nothing empty
instance Semigroup (Recognizer a) where
(<>) = both
data Recognition a
= Exact a
| Prefix [Text]
| Invalid
deriving (Show, Functor)
splitCommon :: Text -> Text -> (Text, Text, Text)
splitCommon l r = fromMaybe ("", l, r) $ Text.commonPrefixes l r
recognize :: Text -> Recognizer a -> Recognition a
recognize tx (Branch pf contained children)
= case splitCommon pf tx of
(_, pfsfx, txsfx) -> case Text.uncons txsfx of
Nothing
| Text.null pfsfx
, Just a <- contained -> Exact a
| otherwise -> Prefix $ keys (Branch pfsfx contained children)
Just (c, txrest)
| Text.null pfsfx
, Just rec <- lookup c children
-> recognize txrest rec
_ -> Invalid
single :: Text -> a -> Recognizer a
single tx v = Branch tx (Just $! v) empty
both :: Recognizer a -> Recognizer a -> Recognizer a
both l@(Branch pfl conl chil) r@(Branch pfr conr chir)
| Text.null pfl && null conl && null chil = r
| Text.null pfr && null conr && null chir = l
| otherwise
= case splitCommon pfl pfr of
(common, lsfx, rsfx) -> Branch common contained children
where
contained = (guard (Text.null lsfx) *> conl)
<|> (guard (Text.null rsfx) *> conr)
children = case (Text.uncons lsfx, Text.uncons rsfx) of
(Nothing, Nothing)
-> unionWith both chil chir
(Just (l',lest), Nothing)
-> insertWith (flip both) l' (Branch lest conl chil) chir
(Nothing, Just (r',rest))
-> insertWith both r' (Branch rest conr chir) chil
(Just (l',lest), Just (r',rest))
-> fromList [ (l', Branch lest conl chil)
, (r', Branch rest conr chir)
]
all :: [Recognizer a] -> Recognizer a
all [] = mempty
all [r] = r
all rs = all $ pair rs
where
pair (l:r:rest) = both l r : pair rest
pair rest = rest
fromCommands :: [(Text, a)] -> Recognizer a
fromCommands = all . map (uncurry single)
addCommand :: Text -> a -> Recognizer a -> Recognizer a
addCommand tx v = both $ single tx v
keys :: Recognizer a -> [Text]
keys (Branch pf contained children)
= maybeToList (pf <$ contained)
++ (mappend pf <$> childKeys children)
childKeys :: HashMap Char (Recognizer a) -> [Text]
childKeys children = toList children >>= \(c,rec) -> Text.cons c <$> keys rec