module Yi.Char.Unicode (greek, symbols, subscripts, superscripts, checkAmbs, disamb) where
import Data.List (isPrefixOf)
import Control.Applicative
greek :: [(String, String)]
greek = [(name, unicode) | (_,name,unicode) <- greekData] ++
[ ([leading,shorthand],unicode)
| (Just shorthand,_,unicode) <- greekData
, leading <- ['\'', 'g'] ]
greekData :: [(Maybe Char, String, String)]
greekData = [(Just 'a', "alpha", "α")
,(Just 'b', "beta", "β")
,(Just 'g', "gamma", "γ")
,(Just 'G', "Gamma", "Γ")
,(Just 'd', "delta", "δ")
,(Just 'D', "Delta", "Δ")
,(Just 'e' , "epsilon", "ε")
,(Just 'z', "zeta", "ζ")
,(Just 'N' , "eta", "η")
,(Just 'E' , "eta", "η")
,(Nothing , "theta", "θ")
,(Nothing , "Theta", "Θ")
,(Just 'i', "iota", "ι")
,(Just 'k', "kapa", "κ")
,(Just 'l', "lambda", "λ")
,(Just 'L', "Lambda", "Λ")
,(Just 'm', "mu", "μ")
,(Just 'n', "nu", "ν")
,(Just 'x', "xi", "ξ")
,(Just 'o', "omicron", "ο")
,(Just 'p' , "pi", "π")
,(Just 'P' , "Pi", "Π")
,(Just 'r', "rho", "ρ")
,(Just 's', "sigma", "σ")
,(Just 'S', "Sigma", "Σ")
,(Just 't', "tau", "τ")
,(Just 'f' , "phi", "φ")
,(Just 'F' , "Phi", "Φ")
,(Just 'c', "chi", "χ")
,(Just 'C', "Chi", "Χ")
,(Nothing , "psi", "ψ")
,(Nothing , "Psi", "Ψ")
,(Just 'w', "omega", "ω")
,(Just 'O', "Omega", "Ω")
]
symbols :: [(String, String)]
symbols =
[
("<","⟨")
,(">","⟩")
,("<>","⟨⟩")
,(">>","⟫")
,("<<","⟪")
,("|(","〖")
,(")|","〗")
,("{|", "⦃")
,("|}", "⦄")
,("[[","⟦")
,("]]","⟧")
,("|_","⌊")
,("_|","⌋")
,("|__|","⌊⌋")
,("r|_","⌈")
,("r_|","⌉")
,("r|__|","⌈⌉")
,("[]", "∎")
,("forall", "∀")
,("all", "∀")
,("exists", "∃")
,("rA", "∀")
,("rE", "∃")
,("/rE", "∄")
,("<|","◃")
,("|>","▹")
,("><","⋈")
,("<)", "◅")
,("(>", "▻")
,("v","∨")
,("u","∪")
,("V","⋁")
,("+u","⊎")
,("u[]","⊔")
,("n[]","⊓")
,("^","∧")
,("/\\", "∧")
,("\\/", "∨")
,("o","∘")
,(".","·")
,("x","×")
,("neg","¬")
,("<-","←")
,("->","→")
,("|->","↦")
,("<-|","↤")
,("<--","⟵")
,("-->","⟶")
,("|-->","⟼")
,("==>","⟹")
,("=>","⇒")
,("<=","⇐")
,("<=>","⇔")
,("~>","↝")
,("<~","↜")
,("<-<", "↢")
,(">->", "↣")
,("<->", "↔")
,("|<-", "⇤")
,("->|", "⇥")
,(">>=","↠")
,("c=","⊆")
,("c","⊂")
,("c-","∈")
,("in","∈")
,("/c-","∉")
,("c/=","⊊")
,("rc=","⊇")
,("rc","⊃")
,("rc-","∋")
,("r/c-","∌")
,("rc/=","⊋")
,(">=","≥")
,("=<","≤")
,("c[]","⊏")
,("rc[]","⊐")
,("c[]=","⊑")
,("rc[]=","⊒")
,("/c[]=","⋢")
,("/rc[]=","⋣")
,("c[]/=","⋤")
,("rc[]/=","⋥")
,("=def","≝")
,("=?","≟")
,("==","≡")
,("~~","≈")
,("~-","≃")
,("~=","≅")
,("~","∼")
,("~~","≈")
,("/=","≠")
,("/==","≢")
,(":=","≔")
,("=:","≕")
,("_|_","⊥")
,("Top","⊤")
,("l","ℓ")
,("::","∷")
,(":", "∶")
,("0", "∅")
,("*", "★")
,("/'l","ƛ")
,("d","∂")
,("#b","♭")
,("#f","♮")
,("##","♯")
,("Hot","♨")
,("Cut","✂")
,("Pen","✎")
,("Tick","✓")
,("-","−")
,("\"","“”")
,("r`","′")
,("|-", "⊢")
,("|/-", "⊬")
,("-|", "⊣")
,("|=", "⊨")
,("|/=", "⊭")
,("||-", "⊩")
,("o+","⊕")
,("o-","⊖")
,("ox","⊗")
,("o/","⊘")
,("o*","⊛")
,("o=","⊜")
,("o.","⊙")
,("oo","⊚")
,("[+]","⊞")
,("[-]","⊟")
,("[x]","⊠")
,("[.]","⊡")
,("[]","∎")
] ++ [ (leading:l, [u]) | leading <- ['|','b'], (l,u) <-
[("N",'ℕ')
,("H",'ℍ')
,("P",'ℙ')
,("R",'ℝ')
,("D",'ⅅ')
,("Q",'ℚ')
,("Z",'ℤ')
,("gg",'ℽ')
,("gG",'ℾ')
,("gP",'ℿ')
,("gS",'⅀')
]
] ++ [
("cP","℘")
,("cL","ℒ")
,("cR","ℛ")
]
checkAmbs :: [(String, String)] -> [(String, String)]
checkAmbs table = check
where ambs = [ (x, y)
| v@(x, _) <- table
, w@(y, _) <- table
, v /= w
, x `isPrefixOf` y ]
check | null ambs = table
| otherwise = error $ "checkAmbs: ambiguous declarations for " ++ show ambs
disamb :: [(String, String)] -> [(String, String)]
disamb table = map f table
where f v@(x, vx) =
let ambs = [ w
| w@(y, _) <- table
, v /= w
, x `isPrefixOf` y ]
in if null ambs then v else (x ++ " ", vx)
zipscripts :: Char -> String -> String -> [(String, String)]
zipscripts c ascii unicode
= zip (fmap ((c:) . pure) ascii) (fmap pure unicode)
subscripts, superscripts :: [(String, String)]
subscripts = zipscripts '_' "0123456789+-=()aeioruvx"
"₀₁₂₃₄₅₆₇₈₉₊₋₌₍₎ₐₑᵢₒᵣᵤᵥₓ"
superscripts = zipscripts '^'
"0123456789+-=()abcdefghijklmnoprstuvwxyzABDEGHIJKLMNOPRTUW"
"⁰¹²³⁴⁵⁶⁷⁸⁹⁺⁻⁼⁽⁾ᵃᵇᶜᵈᵉᶠᵍʰⁱʲᵏˡᵐⁿᵒᵖʳˢᵗᵘᵛʷˣʸᶻᴬᴮᴰᴱᴳᴴᴵᴶᴷᴸᴹᴺᴼᴾᴿᵀᵁᵂ"