Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
http://www.unicode.org/charts/PDF/U1D100.pdf
These symbols are in http://www.gnu.org/software/freefont/, debian=ttf-freefont.
Synopsis
- non_breaking_hypen :: Char
- non_breaking_space :: Char
- middle_dot :: Char
- superscript_digits :: [Char]
- int_show_superscript :: Int -> String
- subscript_digits :: [Char]
- combining_overline :: Char
- overline :: String -> String
- combining_underline :: Char
- underline :: String -> String
- type Unicode_Index = Int
- type Unicode_Name = String
- type Unicode_Range = (Unicode_Index, Unicode_Index)
- type Unicode_Point = (Unicode_Index, Unicode_Name)
- type Unicode_Table = [Unicode_Point]
- unicode_data_table_read :: FilePath -> IO Unicode_Table
- unicode_table_block :: (Unicode_Index, Unicode_Index) -> Unicode_Table -> Unicode_Table
- unicode_point_hs :: Unicode_Point -> String
- unicode_table_hs :: Unicode_Table -> String
- music_tbl :: [Unicode_Table]
- accidentals_rng_set :: [Unicode_Range]
- barlines_rng :: Unicode_Range
- barlines_tbl :: Unicode_Table
- accidentals_tbl :: Unicode_Table
- notes_rng :: Unicode_Range
- notes_tbl :: Unicode_Table
- rests_rng :: Unicode_Range
- rests_tbl :: Unicode_Table
- augmentation_dot :: Unicode_Point
- clefs_rng :: Unicode_Range
- clefs_tbl :: Unicode_Table
- noteheads_rng :: Unicode_Range
- noteheads_tbl :: Unicode_Table
- stem :: Unicode_Point
- dynamics_rng :: Unicode_Range
- dynamics_tbl :: Unicode_Table
- articulations_rng :: Unicode_Range
- articulations_tbl :: Unicode_Table
- ix_set_to_tbl :: Unicode_Table -> [Unicode_Index] -> Unicode_Table
- dot_operator :: Char
- math_plain_ix :: [Unicode_Index]
- math_plain_tbl :: Unicode_Table
- type Unicode_Block = (Unicode_Range, String)
- unicode_blocks :: [Unicode_Block]
- bagua :: Unicode_Block
- bagua_tbl :: Unicode_Table
- yijing :: Unicode_Block
- yijing_tbl :: Unicode_Table
Non-music
non_breaking_hypen :: Char Source #
Unicode non breaking hypen character.
non_breaking_hypen == '‑'
non_breaking_space :: Char Source #
Unicode non breaking space character.
non_breaking_space == ' '
middle_dot :: Char Source #
Unicode interpunct.
middle_dot == '·'
superscript_digits :: [Char] Source #
The superscript variants of the digits 0-9
int_show_superscript :: Int -> String Source #
Map show
of Int
to superscript_digits
.
unwords (map int_show_superscript [0,12,345,6789]) == "⁰ ¹² ³⁴⁵ ⁶⁷⁸⁹"
subscript_digits :: [Char] Source #
The subscript variants of the digits 0-9
combining_overline :: Char Source #
The combining over line character.
['1',combining_overline] == "1̅" ['A',combining_overline] == "A̅"
overline :: String -> String Source #
Add combining_overline
to each Char
.
overline "1234" == "1̅2̅3̅4̅"
combining_underline :: Char Source #
The combining under line character.
['1',combining_underline] == "1̲"
underline :: String -> String Source #
Add combining_underline
to each Char
.
underline "1234" == "1̲2̲3̲4̲"
Table
type Unicode_Index = Int Source #
type Unicode_Name = String Source #
type Unicode_Range = (Unicode_Index, Unicode_Index) Source #
type Unicode_Point = (Unicode_Index, Unicode_Name) Source #
type Unicode_Table = [Unicode_Point] Source #
unicode_data_table_read :: FilePath -> IO Unicode_Table Source #
http://unicode.org/Public/11.0.0/ucd/UnicodeData.txt
let fn = "/home/rohan/data/unicode.org/Public/11.0.0/ucd/UnicodeData.txt" tbl <- unicode_data_table_read fn length tbl == 32292 T.reverse_lookup_err "MIDDLE DOT" tbl == 0x00B7 putStrLn $ unwords $ map (\(n,x) -> toEnum n : x) $ filter (\(_,x) -> "EMPTY SET" `isInfixOf` x) tbl T.lookup_err 0x22C5 tbl == "DOT OPERATOR"
Music
music_tbl :: [Unicode_Table] Source #
barlines_tbl :: Unicode_Table Source #
UNICODE barline symbols.
let r = "𝄀𝄁𝄂𝄃𝄄𝄅" in map (toEnum . fst) barlines_tbl == r
accidentals_tbl :: Unicode_Table Source #
UNICODE accidental symbols.
let r = "♭♮♯𝄪𝄫𝄬𝄭𝄮𝄯𝄰𝄱𝄲𝄳" in map (toEnum . fst) accidentals_tbl == r
notes_tbl :: Unicode_Table Source #
UNICODE note duration symbols.
let r = "𝅜𝅝𝅗𝅥𝅘𝅥𝅘𝅥𝅮𝅘𝅥𝅯𝅘𝅥𝅰𝅘𝅥𝅱𝅘𝅥𝅲" in map (toEnum . fst) notes_tbl == r
rests_tbl :: Unicode_Table Source #
UNICODE rest symbols.
let r = "𝄻𝄼𝄽𝄾𝄿𝅀𝅁𝅂" in map (toEnum . fst) rests_tbl == r
augmentation_dot :: Unicode_Point Source #
Augmentation dot.
map toEnum [0x1D15E,0x1D16D,0x1D16D] == "𝅗𝅥𝅭𝅭"
clefs_tbl :: Unicode_Table Source #
UNICODE clef symbols.
let r = "𝄞𝄟𝄠𝄡𝄢𝄣𝄤𝄥𝄦" in map (toEnum . fst) clefs_tbl == r
noteheads_tbl :: Unicode_Table Source #
UNICODE notehead symbols.
let r = "𝅃𝅄𝅅𝅆𝅇𝅈𝅉𝅊𝅋𝅌𝅍𝅎𝅏𝅐𝅑𝅒𝅓𝅔𝅕𝅖𝅗𝅘𝅙𝅚𝅛" in map (toEnum . fst) noteheads_tbl == r
stem :: Unicode_Point Source #
Math
ix_set_to_tbl :: Unicode_Table -> [Unicode_Index] -> Unicode_Table Source #
dot_operator :: Char Source #
Unicode dot-operator.
dot_operator == '⋅'
math_plain_ix :: [Unicode_Index] Source #
Math symbols outside of the math blocks.
putStrLn (unicode_table_hs (ix_set_to_tbl tbl math_plain_ix))
Blocks
type Unicode_Block = (Unicode_Range, String) Source #
BAGUA, EIGHT TRI-GRAMS
bagua :: Unicode_Block Source #
Bagua tri-grams.
putStrLn $ unicode_table_hs (unicode_table_block (fst bagua) tbl)
bagua_tbl :: Unicode_Table Source #
Table of eight tri-grams.
HEAVEN,乾,Qián,☰,111 LAKE,兌,Duì,☱,110 FIRE,離,Lí,☲,101 THUNDER,震,Zhèn,☳,100 WIND,巽,Xùn,☴,011 WATER,坎,Kǎn,☵,010 MOUNTAIN,艮,Gèn,☶,001 EARTH,坤,Kūn,☷,000
YIJING (I-CHING), SIXTY-FOUR HEXAGRAMS
yijing :: Unicode_Block Source #
Yijing hexagrams in King Wen sequence.
putStrLn $ unicode_table_hs (unicode_table_block (fst yijing) tbl)
yijing_tbl :: Unicode_Table Source #
Yijing hexagrams in King Wen sequence.
䷀,乾,qián,111,111 ䷁,坤,kūn,000,000 ䷂,屯,chún,100,010 ䷃,蒙,méng,010,001 ䷄,需,xū,111,010 ䷅,訟,sòng,010,111 ䷆,師,shī,010,000 ䷇,比,bǐ,000,010 ䷈,小畜,xiǎo chù,111,011 ䷉,履,lǚ,110,111 ䷊,泰,tài,111,000 ䷋,否,pǐ,000,111 ䷌,同人,tóng rén,101,111 ䷍,大有,dà yǒu,111,101 ䷎,謙,qiān,001,000 ䷏,豫,yù,000,100 ䷐,隨,suí,100,110 ䷑,蠱,gŭ,011,001 ䷒,臨,lín,110,000 ䷓,觀,guān,000,011 ䷔,噬嗑,shì kè,100,101 ䷕,賁,bì,101,001 ䷖,剝,bō,000,001 ䷗,復,fù,100,000 ䷘,無妄,wú wàng,100,111 ䷙,大畜,dà chù,111,001 ䷚,頤,yí,100,001 ䷛,大過,dà guò,011,110 ䷜,坎,kǎn,010,010 ䷝,離,lí,101,101 ䷞,咸,xián,001,110 ䷟,恆,héng,011,100 ䷠,遯,dùn,001,111 ䷡,大壯,dà zhuàng,111,100 ䷢,晉,jìn,000,101 ䷣,明夷,míng yí,101,000 ䷤,家人,jiā rén,101,011 ䷥,睽,kuí,110,101 ䷦,蹇,jiǎn,001,010 ䷧,解,xiè,010,100 ䷨,損,sǔn,110,001 ䷩,益,yì,100,011 ䷪,夬,guài,111,110 ䷫,姤,gòu,011,111 ䷬,萃,cuì,000,110 ䷭,升,shēng,011,000 ䷮,困,kùn,010,110 ䷯,井,jǐng,011,010 ䷰,革,gé,101,110 ䷱,鼎,dǐng,011,101 ䷲,震,zhèn,100,100 ䷳,艮,gèn,001,001 ䷴,漸,jiàn,001,011 ䷵,歸妹,guī mèi,110,100 ䷶,豐,fēng,101,100 ䷷,旅,lǚ,001,101 ䷸,巽,xùn,011,011 ䷹,兌,duì,110,110 ䷺,渙,huàn,010,011 ䷻,節,jié,110,010 ䷼,中孚,zhōng fú,110,011 ䷽,小過,xiǎo guò,001,110 ䷾,既濟,jì jì,101,010 ䷿,未濟,wèi jì,010,101