mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-08-05 14:41:54 -07:00
XMonad.Prompt.Unicode: respect searchPredicate and sorter from XPConfig
This commit is contained in:
@@ -96,20 +96,27 @@ parseUnicodeData = mapMaybe parseLine . BS.lines
|
||||
[(c,"")] <- return . readHex $ BS.unpack field1
|
||||
return (chr c, field2)
|
||||
|
||||
searchUnicode :: [(Char, BS.ByteString)] -> String -> [(Char, String)]
|
||||
searchUnicode entries s = map (second BS.unpack) $ filter go entries
|
||||
where w = map BS.pack . filter (all isAscii) . filter ((> 1) . length) . words $ map toUpper s
|
||||
go (c,d) = all (`BS.isInfixOf` d) w
|
||||
type Predicate = String -> String -> Bool
|
||||
|
||||
searchUnicode :: [(Char, BS.ByteString)] -> Predicate -> String -> [(Char, String)]
|
||||
searchUnicode entries p s = map (second BS.unpack) $ filter go entries
|
||||
where w = filter (all isAscii) . filter ((> 1) . length) . words $ map toUpper s
|
||||
go (c,d) = all (`p` (BS.unpack d)) w
|
||||
|
||||
mkUnicodePrompt :: String -> [String] -> String -> XPConfig -> X ()
|
||||
mkUnicodePrompt prog args unicodeDataFilename config =
|
||||
whenX (populateEntries unicodeDataFilename) $ do
|
||||
entries <- fmap getUnicodeData (XS.get :: X UnicodeData)
|
||||
mkXPrompt Unicode config (unicodeCompl entries) paste
|
||||
mkXPrompt
|
||||
Unicode
|
||||
(config {sorter = sorter config . map toUpper})
|
||||
(unicodeCompl entries $ searchPredicate config)
|
||||
paste
|
||||
where
|
||||
unicodeCompl _ [] = return []
|
||||
unicodeCompl entries s = do
|
||||
let m = searchUnicode entries s
|
||||
unicodeCompl :: [(Char, BS.ByteString)] -> Predicate -> String -> IO [String]
|
||||
unicodeCompl _ _ "" = return []
|
||||
unicodeCompl entries p s = do
|
||||
let m = searchUnicode entries p s
|
||||
return . map (\(c,d) -> printf "%s %s" [c] d) $ take 20 m
|
||||
paste [] = return ()
|
||||
paste (c:_) = liftIO $ do
|
||||
|
Reference in New Issue
Block a user