Skip to content

Commit

Permalink
Update keysymdef parsing (#28)
Browse files Browse the repository at this point in the history
  • Loading branch information
39aldo39 committed Apr 2, 2020
1 parent a8ad8c8 commit 690aba3
Show file tree
Hide file tree
Showing 2 changed files with 10 additions and 48 deletions.
16 changes: 9 additions & 7 deletions scripts/ParseKeysymdef.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,28 +5,30 @@ module ParseKeysymdef where
import Prelude.Unicode

import Data.Char (chr)
import Data.Void (Void)
import Text.Read (readMaybe)
import qualified Data.Text.Lazy.IO as L (readFile)
import Control.Applicative (liftA2)
import Text.Megaparsec
import Text.Megaparsec.Text.Lazy (Parser)
import Text.Megaparsec.Char

type Parser = Parsec Void String

main IO ()
main =
parseFromFile symLines "/usr/include/X11/keysymdef.h" >>=
either (print parseErrorPretty) (mapM_ (\(s,c) putStrLn (replicate 4 ' ' ", ('" [c] "', " show s ")")))
either (print errorBundlePretty) (mapM_ (\(s,c) putStrLn (replicate 4 ' ' ", ('" [c] "', " show s ")")))

symLine Parser [(String, Char)]
symLine = (:[]) <$> liftA2 (,)
(string "#define XK_" *> many (alphaNumChar <|> char '_') <* space <* many alphaNumChar <* space)
(fmap f (string "/*" *> space *> optional (char '(') *> space *> string "U+" *> many alphaNumChar <* manyTill anyChar eol))
(fmap f (string "/*" *> space *> string "U+" *> many alphaNumChar <* manyTill anySingle eol))
where f xs = maybe '\0' chr (readMaybe ('0':'x':xs))

symLines Parser [(String, Char)]
symLines = concat <$> many (try symLine <|> [] <$ manyTill anyChar eol)
symLines = concat <$> many (try symLine <|> [] <$ manyTill anySingle eol)

printLines [(String, Char)] String
printLines = unlines map (\(s, c) " , ('" [c] "', " show s ")")

parseFromFile Parser α String IO (Either (ParseError Char Dec) α)
parseFromFile p fname = parse p "" <$> L.readFile fname
parseFromFile Parser α String IO (Either (ParseErrorBundle String Void) α)
parseFromFile p fname = parse p "" <$> readFile fname
42 changes: 1 addition & 41 deletions src/Lookup/Linux.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1541,11 +1541,8 @@ charAndString =
, ('ψ', "Greek_psi")
, ('ω', "Greek_omega")
, ('', "leftradical")
, ('', "topleftradical")
, ('', "horizconnector")
, ('', "topintegral")
, ('', "botintegral")
, ('', "vertconnector")
, ('', "topleftsqbracket")
, ('', "botleftsqbracket")
, ('', "toprightsqbracket")
Expand Down Expand Up @@ -1615,7 +1612,6 @@ charAndString =
, (' ', "hairspace")
, ('', "emdash")
, ('', "endash")
, ('', "signifblank")
, ('', "ellipsis")
, ('', "doubbaselinedot")
, ('⅓', "onethird")
Expand All @@ -1628,19 +1624,11 @@ charAndString =
, ('⅚', "fivesixths")
, ('', "careof")
, ('', "figdash")
, ('', "leftanglebracket")
, ('.', "decimalpoint")
, ('', "rightanglebracket")
, ('⅛', "oneeighth")
, ('⅜', "threeeighths")
, ('⅝', "fiveeighths")
, ('⅞', "seveneighths")
, ('', "trademark")
, ('', "signaturemark")
, ('', "leftopentriangle")
, ('', "rightopentriangle")
, ('', "emopencircle")
, ('', "emopenrectangle")
, ('', "leftsinglequotemark")
, ('', "rightsinglequotemark")
, ('', "leftdoublequotemark")
Expand All @@ -1650,23 +1638,6 @@ charAndString =
, ('', "minutes")
, ('', "seconds")
, ('', "latincross")
, ('', "filledrectbullet")
, ('', "filledlefttribullet")
, ('', "filledrighttribullet")
, ('', "emfilledcircle")
, ('', "emfilledrect")
, ('', "enopencircbullet")
, ('', "enopensquarebullet")
, ('', "openrectbullet")
, ('', "opentribulletup")
, ('', "opentribulletdown")
, ('', "openstar")
, ('', "enfilledcircbullet")
, ('', "enfilledsqbullet")
, ('', "filledtribulletup")
, ('', "filledtribulletdown")
, ('', "leftpointer")
, ('', "rightpointer")
, ('', "club")
, ('', "diamond")
, ('', "heart")
Expand All @@ -1685,23 +1656,13 @@ charAndString =
, ('', "caret")
, ('', "singlelowquotemark")
, ('', "doublelowquotemark")
, ('<', "leftcaret")
, ('>', "rightcaret")
, ('', "downcaret")
, ('', "upcaret")
, ('¯', "overbar")
, ('', "downtack")
, ('', "upshoe")
, ('', "downstile")
, ('_', "underbar")
, ('', "jot")
, ('', "quad")
, ('', "uptack")
, ('', "circle")
, ('', "upstile")
, ('', "downshoe")
, ('', "rightshoe")
, ('', "leftshoe")
, ('', "lefttack")
, ('', "righttack")
, ('', "hebrew_doublelowline")
Expand Down Expand Up @@ -1815,7 +1776,6 @@ charAndString =
, ('๗', "Thai_lekchet")
, ('๘', "Thai_lekpaet")
, ('๙', "Thai_lekkao")
, ('', "Korean_Won")
, ('և', "Armenian_ligature_ew")
, ('։', "Armenian_full_stop")
, ('։', "Armenian_verjaket")
Expand Down Expand Up @@ -1949,7 +1909,7 @@ charAndString =
, ('Ĭ', "Ibreve")
, ('Ƶ', "Zstroke")
, ('Ǧ', "Gcaron")
, ('ǒ', "Ocaron")
, ('Ǒ', "Ocaron")
, ('Ɵ', "Obarred")
, ('ẋ', "xabovedot")
, ('ĭ', "ibreve")
Expand Down

0 comments on commit 690aba3

Please sign in to comment.