Navigation Menu

Skip to content

Instantly share code, notes, and snippets.

@mrkgnao
Last active November 8, 2022 18:28
Show Gist options
  • Star 44 You must be signed in to star a gist
  • Fork 8 You must be signed in to fork a gist
  • Save mrkgnao/49c7480e1df42405a36b7ab09fe87f3d to your computer and use it in GitHub Desktop.
Save mrkgnao/49c7480e1df42405a36b7ab09fe87f3d to your computer and use it in GitHub Desktop.
Render Iosevka ligatures to Private Use Area glyphs, for Emacs

Load IosevkaConfigGen.hs in a REPL and run toToml or toElisp to generate either TOML definitions for the glyphs (to put in parameters.toml), or a list of prettify-symbol-mode definitions for Emacs.

An example of generated TOML glyph definitions and elisp code are provided.

screenshot

Note that

  • I have a feature set called XALL in my fork that basically enables every possible ligation.

  • I've hacked a few extra ligatures into my local checkout (including <<, >>, a few attempts to make more ->>--ish things a la Fira Code and Pragmata Pro, and also ligatures for <<< and >>> with a bit of extra space between the arrows because things look ugly without).

  • I'm generating far more glyphs than there are ligatures for. In particular, I've added definitions for lots of things like <~> which aren't yet in Iosevka. The cool thing is that the generated glyphs end up looking almost exactly the same as "plain text". That is, plain <| and prettify-symbols-mode-enabled Unicode <| look the same. Once Iosevka gets those ligatures, I can just recompile Iosevka without having to change anything. (Besides restarting Emacs, ha.)

  • A ton of the generated glyphs (hello ==>>>--) are stupid, but meh. I suppose having Pragmata-like equals chains with little indents near the end of each = might make those useful in Some Future ASCII APL/Haskell ("Jaskell"?) :P

{-# LANGUAGE RecordWildCards, Arrows #-}
import Numeric
import Data.Char
import Control.Monad
import Data.Monoid ((<>))
import Data.List (nub, sort, reverse)
data RepeatBounds = RB
{ str :: String
, min :: Int
, max :: Int
} deriving Show
repeatFromTo s (min,max) = map (\n -> concat $ replicate n s) [min .. max]
tripleOp left mid right = [left <> mid, left <> mid <> right, mid <> right]
extended xs = map concat $ mapM renderGroup xs
where renderGroup RB{..} = repeatFromTo str (min,max)
reverseArrow = reverse . map rev
where
rev xs =
case xs of
'>' -> '<'
'<' -> '>'
x -> x
angleArrows = rights <> map reverseArrow rights
where
rights = nub $
[rgLeftHyphen, rgLeftHyphen', rgLeftEquals, rgLeftEquals'] >>= extended
rgLeftHyphen = [RB "-" 1 2, RB ">" 1 3, RB "-" 0 2]
rgLeftHyphen' = [RB "-" 0 2, RB ">" 1 3, RB "-" 1 2]
rgLeftEquals = [RB "=" 1 2, RB ">" 1 3, RB "=" 0 2]
rgLeftEquals' = [RB "=" 0 2, RB ">" 1 3, RB "=" 1 2]
rgLeftTilde = [RB "~" 1 2, RB ">" 1 3, RB "-" 0 2]
rgLeftTilde' = [RB "~" 1 2, RB ">" 1 3, RB "-" 0 0]
doubleEnded left mid right min max = do
body <- mid `repeatFromTo` (min,max)
pure (left ++ body ++ right)
rightEnded right mid = doubleEnded "" mid right
leftEnded left mid = doubleEnded left mid ""
hyphenDouble = doubleEnded "<" "-" ">" 1 5
equalsDouble = doubleEnded "<" "=" ">" 1 5
asteriskDouble = doubleEnded "<" "*" ">" 2 5
htmlCommentStart = leftEnded "<!" "-" 2 3
colons = repeatFromTo ":" (2,4)
dots = repeatFromTo "." (2,4)
tripleOps =
concatMap
(\mid -> tripleOp "<" mid ">")
["$", ".", "*", "\\", "/", "\"", "'", "^", "&", "%", "@", "#", "+", "-", "!", "?", "|", ":"]
lensOps =
concat
[ prefix' ":" "+-="
, postfix' ":" "+-="
, prefix' "=" "^+-*/%"
, postfix' "=" "^+-*/%"
]
where
prefix str = map (str ++)
prefix' str = prefix str . lift
postfix str = map (++ str)
postfix' str = postfix str . lift
lift = map (: [])
addReversed xs = nub $ xs <> map reverseArrow xs
monadics = addReversed [">=>", ">->",">-->",">==>"]
composition = addReversed [">>", ">>>"]
logic = ["/\\", "\\/"]
semigroups = ["<>"] <> tripleOp "<" "+" ">"
allSeqs =
[ ("Double-ended hyphen arrows", hyphenDouble)
, ("Double-ended equals arrows",equalsDouble)
, ("Double-ended asterisk operators",asteriskDouble)
, ("HTML comments",htmlCommentStart)
, ("Three-char ops with discards",tripleOps)
, ("Colons",colons)
, ("Arrow-like operators",angleArrows)
, ("Monadic operators", monadics)
, ("Composition operators", composition)
, ("Lens operators",lensOps)
, ("Logical", logic)
, ("Semigroup/monoid operators", semigroups)
]
toToml = foldM_ go puaStart allSeqs
where
go start (sectionHeader, ligs) = do
putStrLn "# -----------------------------------------"
putStrLn $ "# " <> sectionHeader
putStrLn "# -----------------------------------------\n"
forM_ (enumerate start ligs) $ \(ix, lig) -> do
putStrLn "[[iosevka.compLig]]"
putStrLn $ "unicode = " <> show ix <> " # " <> toHex' "0x" ix
putStrLn "featureTag = 'XALL'"
putStrLn $ "sequence = " <> show lig
putStrLn ""
return $ start + length ligs
toElisp = foldM_ go puaStart allSeqs
where
go start (sectionHeader, ligs) = do
putStrLn $ "\n;; " <> sectionHeader <> " ----------------"
forM_ (enumerate start ligs) $ \(ix, lig) ->
putStrLn $ "(" <> show lig <> " . " <> toHex' "#X" ix <> ")"
return $ start + length ligs
enumerate start = zip [start ..]
puaStart = 0xE100
toHex n = showHex n ""
toHex' prefix = (prefix <>) . toHex
# -----------------------------------------
# Double-ended hyphen arrows
# -----------------------------------------
[[iosevka.compLig]]
unicode = 57600 # 0xe100
featureTag = 'XALL'
sequence = "<->"
[[iosevka.compLig]]
unicode = 57601 # 0xe101
featureTag = 'XALL'
sequence = "<-->"
[[iosevka.compLig]]
unicode = 57602 # 0xe102
featureTag = 'XALL'
sequence = "<--->"
[[iosevka.compLig]]
unicode = 57603 # 0xe103
featureTag = 'XALL'
sequence = "<---->"
[[iosevka.compLig]]
unicode = 57604 # 0xe104
featureTag = 'XALL'
sequence = "<----->"
# -----------------------------------------
# Double-ended equals arrows
# -----------------------------------------
[[iosevka.compLig]]
unicode = 57605 # 0xe105
featureTag = 'XALL'
sequence = "<=>"
[[iosevka.compLig]]
unicode = 57606 # 0xe106
featureTag = 'XALL'
sequence = "<==>"
[[iosevka.compLig]]
unicode = 57607 # 0xe107
featureTag = 'XALL'
sequence = "<===>"
[[iosevka.compLig]]
unicode = 57608 # 0xe108
featureTag = 'XALL'
sequence = "<====>"
[[iosevka.compLig]]
unicode = 57609 # 0xe109
featureTag = 'XALL'
sequence = "<=====>"
# -----------------------------------------
# Double-ended asterisk operators
# -----------------------------------------
[[iosevka.compLig]]
unicode = 57610 # 0xe10a
featureTag = 'XALL'
sequence = "<**>"
[[iosevka.compLig]]
unicode = 57611 # 0xe10b
featureTag = 'XALL'
sequence = "<***>"
[[iosevka.compLig]]
unicode = 57612 # 0xe10c
featureTag = 'XALL'
sequence = "<****>"
[[iosevka.compLig]]
unicode = 57613 # 0xe10d
featureTag = 'XALL'
sequence = "<*****>"
# -----------------------------------------
# HTML comments
# -----------------------------------------
[[iosevka.compLig]]
unicode = 57614 # 0xe10e
featureTag = 'XALL'
sequence = "<!--"
[[iosevka.compLig]]
unicode = 57615 # 0xe10f
featureTag = 'XALL'
sequence = "<!---"
# -----------------------------------------
# Three-char ops with discards
# -----------------------------------------
[[iosevka.compLig]]
unicode = 57616 # 0xe110
featureTag = 'XALL'
sequence = "<$"
[[iosevka.compLig]]
unicode = 57617 # 0xe111
featureTag = 'XALL'
sequence = "<$>"
[[iosevka.compLig]]
unicode = 57618 # 0xe112
featureTag = 'XALL'
sequence = "$>"
[[iosevka.compLig]]
unicode = 57619 # 0xe113
featureTag = 'XALL'
sequence = "<."
[[iosevka.compLig]]
unicode = 57620 # 0xe114
featureTag = 'XALL'
sequence = "<.>"
[[iosevka.compLig]]
unicode = 57621 # 0xe115
featureTag = 'XALL'
sequence = ".>"
[[iosevka.compLig]]
unicode = 57622 # 0xe116
featureTag = 'XALL'
sequence = "<*"
[[iosevka.compLig]]
unicode = 57623 # 0xe117
featureTag = 'XALL'
sequence = "<*>"
[[iosevka.compLig]]
unicode = 57624 # 0xe118
featureTag = 'XALL'
sequence = "*>"
[[iosevka.compLig]]
unicode = 57625 # 0xe119
featureTag = 'XALL'
sequence = "<\\"
[[iosevka.compLig]]
unicode = 57626 # 0xe11a
featureTag = 'XALL'
sequence = "<\\>"
[[iosevka.compLig]]
unicode = 57627 # 0xe11b
featureTag = 'XALL'
sequence = "\\>"
[[iosevka.compLig]]
unicode = 57628 # 0xe11c
featureTag = 'XALL'
sequence = "</"
[[iosevka.compLig]]
unicode = 57629 # 0xe11d
featureTag = 'XALL'
sequence = "</>"
[[iosevka.compLig]]
unicode = 57630 # 0xe11e
featureTag = 'XALL'
sequence = "/>"
[[iosevka.compLig]]
unicode = 57631 # 0xe11f
featureTag = 'XALL'
sequence = "<\""
[[iosevka.compLig]]
unicode = 57632 # 0xe120
featureTag = 'XALL'
sequence = "<\">"
[[iosevka.compLig]]
unicode = 57633 # 0xe121
featureTag = 'XALL'
sequence = "\">"
[[iosevka.compLig]]
unicode = 57634 # 0xe122
featureTag = 'XALL'
sequence = "<'"
[[iosevka.compLig]]
unicode = 57635 # 0xe123
featureTag = 'XALL'
sequence = "<'>"
[[iosevka.compLig]]
unicode = 57636 # 0xe124
featureTag = 'XALL'
sequence = "'>"
[[iosevka.compLig]]
unicode = 57637 # 0xe125
featureTag = 'XALL'
sequence = "<^"
[[iosevka.compLig]]
unicode = 57638 # 0xe126
featureTag = 'XALL'
sequence = "<^>"
[[iosevka.compLig]]
unicode = 57639 # 0xe127
featureTag = 'XALL'
sequence = "^>"
[[iosevka.compLig]]
unicode = 57640 # 0xe128
featureTag = 'XALL'
sequence = "<&"
[[iosevka.compLig]]
unicode = 57641 # 0xe129
featureTag = 'XALL'
sequence = "<&>"
[[iosevka.compLig]]
unicode = 57642 # 0xe12a
featureTag = 'XALL'
sequence = "&>"
[[iosevka.compLig]]
unicode = 57643 # 0xe12b
featureTag = 'XALL'
sequence = "<%"
[[iosevka.compLig]]
unicode = 57644 # 0xe12c
featureTag = 'XALL'
sequence = "<%>"
[[iosevka.compLig]]
unicode = 57645 # 0xe12d
featureTag = 'XALL'
sequence = "%>"
[[iosevka.compLig]]
unicode = 57646 # 0xe12e
featureTag = 'XALL'
sequence = "<@"
[[iosevka.compLig]]
unicode = 57647 # 0xe12f
featureTag = 'XALL'
sequence = "<@>"
[[iosevka.compLig]]
unicode = 57648 # 0xe130
featureTag = 'XALL'
sequence = "@>"
[[iosevka.compLig]]
unicode = 57649 # 0xe131
featureTag = 'XALL'
sequence = "<#"
[[iosevka.compLig]]
unicode = 57650 # 0xe132
featureTag = 'XALL'
sequence = "<#>"
[[iosevka.compLig]]
unicode = 57651 # 0xe133
featureTag = 'XALL'
sequence = "#>"
[[iosevka.compLig]]
unicode = 57652 # 0xe134
featureTag = 'XALL'
sequence = "<+"
[[iosevka.compLig]]
unicode = 57653 # 0xe135
featureTag = 'XALL'
sequence = "<+>"
[[iosevka.compLig]]
unicode = 57654 # 0xe136
featureTag = 'XALL'
sequence = "+>"
[[iosevka.compLig]]
unicode = 57655 # 0xe137
featureTag = 'XALL'
sequence = "<-"
[[iosevka.compLig]]
unicode = 57656 # 0xe138
featureTag = 'XALL'
sequence = "<->"
[[iosevka.compLig]]
unicode = 57657 # 0xe139
featureTag = 'XALL'
sequence = "->"
[[iosevka.compLig]]
unicode = 57658 # 0xe13a
featureTag = 'XALL'
sequence = "<!"
[[iosevka.compLig]]
unicode = 57659 # 0xe13b
featureTag = 'XALL'
sequence = "<!>"
[[iosevka.compLig]]
unicode = 57660 # 0xe13c
featureTag = 'XALL'
sequence = "!>"
[[iosevka.compLig]]
unicode = 57661 # 0xe13d
featureTag = 'XALL'
sequence = "<?"
[[iosevka.compLig]]
unicode = 57662 # 0xe13e
featureTag = 'XALL'
sequence = "<?>"
[[iosevka.compLig]]
unicode = 57663 # 0xe13f
featureTag = 'XALL'
sequence = "?>"
[[iosevka.compLig]]
unicode = 57664 # 0xe140
featureTag = 'XALL'
sequence = "<|"
[[iosevka.compLig]]
unicode = 57665 # 0xe141
featureTag = 'XALL'
sequence = "<|>"
[[iosevka.compLig]]
unicode = 57666 # 0xe142
featureTag = 'XALL'
sequence = "|>"
[[iosevka.compLig]]
unicode = 57667 # 0xe143
featureTag = 'XALL'
sequence = "<:"
[[iosevka.compLig]]
unicode = 57668 # 0xe144
featureTag = 'XALL'
sequence = "<:>"
[[iosevka.compLig]]
unicode = 57669 # 0xe145
featureTag = 'XALL'
sequence = ":>"
# -----------------------------------------
# Colons
# -----------------------------------------
[[iosevka.compLig]]
unicode = 57670 # 0xe146
featureTag = 'XALL'
sequence = "::"
[[iosevka.compLig]]
unicode = 57671 # 0xe147
featureTag = 'XALL'
sequence = ":::"
[[iosevka.compLig]]
unicode = 57672 # 0xe148
featureTag = 'XALL'
sequence = "::::"
# -----------------------------------------
# Arrow-like operators
# -----------------------------------------
[[iosevka.compLig]]
unicode = 57673 # 0xe149
featureTag = 'XALL'
sequence = "->"
[[iosevka.compLig]]
unicode = 57674 # 0xe14a
featureTag = 'XALL'
sequence = "->-"
[[iosevka.compLig]]
unicode = 57675 # 0xe14b
featureTag = 'XALL'
sequence = "->--"
[[iosevka.compLig]]
unicode = 57676 # 0xe14c
featureTag = 'XALL'
sequence = "->>"
[[iosevka.compLig]]
unicode = 57677 # 0xe14d
featureTag = 'XALL'
sequence = "->>-"
[[iosevka.compLig]]
unicode = 57678 # 0xe14e
featureTag = 'XALL'
sequence = "->>--"
[[iosevka.compLig]]
unicode = 57679 # 0xe14f
featureTag = 'XALL'
sequence = "->>>"
[[iosevka.compLig]]
unicode = 57680 # 0xe150
featureTag = 'XALL'
sequence = "->>>-"
[[iosevka.compLig]]
unicode = 57681 # 0xe151
featureTag = 'XALL'
sequence = "->>>--"
[[iosevka.compLig]]
unicode = 57682 # 0xe152
featureTag = 'XALL'
sequence = "-->"
[[iosevka.compLig]]
unicode = 57683 # 0xe153
featureTag = 'XALL'
sequence = "-->-"
[[iosevka.compLig]]
unicode = 57684 # 0xe154
featureTag = 'XALL'
sequence = "-->--"
[[iosevka.compLig]]
unicode = 57685 # 0xe155
featureTag = 'XALL'
sequence = "-->>"
[[iosevka.compLig]]
unicode = 57686 # 0xe156
featureTag = 'XALL'
sequence = "-->>-"
[[iosevka.compLig]]
unicode = 57687 # 0xe157
featureTag = 'XALL'
sequence = "-->>--"
[[iosevka.compLig]]
unicode = 57688 # 0xe158
featureTag = 'XALL'
sequence = "-->>>"
[[iosevka.compLig]]
unicode = 57689 # 0xe159
featureTag = 'XALL'
sequence = "-->>>-"
[[iosevka.compLig]]
unicode = 57690 # 0xe15a
featureTag = 'XALL'
sequence = "-->>>--"
[[iosevka.compLig]]
unicode = 57691 # 0xe15b
featureTag = 'XALL'
sequence = ">-"
[[iosevka.compLig]]
unicode = 57692 # 0xe15c
featureTag = 'XALL'
sequence = ">--"
[[iosevka.compLig]]
unicode = 57693 # 0xe15d
featureTag = 'XALL'
sequence = ">>-"
[[iosevka.compLig]]
unicode = 57694 # 0xe15e
featureTag = 'XALL'
sequence = ">>--"
[[iosevka.compLig]]
unicode = 57695 # 0xe15f
featureTag = 'XALL'
sequence = ">>>-"
[[iosevka.compLig]]
unicode = 57696 # 0xe160
featureTag = 'XALL'
sequence = ">>>--"
[[iosevka.compLig]]
unicode = 57697 # 0xe161
featureTag = 'XALL'
sequence = "=>"
[[iosevka.compLig]]
unicode = 57698 # 0xe162
featureTag = 'XALL'
sequence = "=>="
[[iosevka.compLig]]
unicode = 57699 # 0xe163
featureTag = 'XALL'
sequence = "=>=="
[[iosevka.compLig]]
unicode = 57700 # 0xe164
featureTag = 'XALL'
sequence = "=>>"
[[iosevka.compLig]]
unicode = 57701 # 0xe165
featureTag = 'XALL'
sequence = "=>>="
[[iosevka.compLig]]
unicode = 57702 # 0xe166
featureTag = 'XALL'
sequence = "=>>=="
[[iosevka.compLig]]
unicode = 57703 # 0xe167
featureTag = 'XALL'
sequence = "=>>>"
[[iosevka.compLig]]
unicode = 57704 # 0xe168
featureTag = 'XALL'
sequence = "=>>>="
[[iosevka.compLig]]
unicode = 57705 # 0xe169
featureTag = 'XALL'
sequence = "=>>>=="
[[iosevka.compLig]]
unicode = 57706 # 0xe16a
featureTag = 'XALL'
sequence = "==>"
[[iosevka.compLig]]
unicode = 57707 # 0xe16b
featureTag = 'XALL'
sequence = "==>="
[[iosevka.compLig]]
unicode = 57708 # 0xe16c
featureTag = 'XALL'
sequence = "==>=="
[[iosevka.compLig]]
unicode = 57709 # 0xe16d
featureTag = 'XALL'
sequence = "==>>"
[[iosevka.compLig]]
unicode = 57710 # 0xe16e
featureTag = 'XALL'
sequence = "==>>="
[[iosevka.compLig]]
unicode = 57711 # 0xe16f
featureTag = 'XALL'
sequence = "==>>=="
[[iosevka.compLig]]
unicode = 57712 # 0xe170
featureTag = 'XALL'
sequence = "==>>>"
[[iosevka.compLig]]
unicode = 57713 # 0xe171
featureTag = 'XALL'
sequence = "==>>>="
[[iosevka.compLig]]
unicode = 57714 # 0xe172
featureTag = 'XALL'
sequence = "==>>>=="
[[iosevka.compLig]]
unicode = 57715 # 0xe173
featureTag = 'XALL'
sequence = ">="
[[iosevka.compLig]]
unicode = 57716 # 0xe174
featureTag = 'XALL'
sequence = ">=="
[[iosevka.compLig]]
unicode = 57717 # 0xe175
featureTag = 'XALL'
sequence = ">>="
[[iosevka.compLig]]
unicode = 57718 # 0xe176
featureTag = 'XALL'
sequence = ">>=="
[[iosevka.compLig]]
unicode = 57719 # 0xe177
featureTag = 'XALL'
sequence = ">>>="
[[iosevka.compLig]]
unicode = 57720 # 0xe178
featureTag = 'XALL'
sequence = ">>>=="
[[iosevka.compLig]]
unicode = 57721 # 0xe179
featureTag = 'XALL'
sequence = "<-"
[[iosevka.compLig]]
unicode = 57722 # 0xe17a
featureTag = 'XALL'
sequence = "-<-"
[[iosevka.compLig]]
unicode = 57723 # 0xe17b
featureTag = 'XALL'
sequence = "--<-"
[[iosevka.compLig]]
unicode = 57724 # 0xe17c
featureTag = 'XALL'
sequence = "<<-"
[[iosevka.compLig]]
unicode = 57725 # 0xe17d
featureTag = 'XALL'
sequence = "-<<-"
[[iosevka.compLig]]
unicode = 57726 # 0xe17e
featureTag = 'XALL'
sequence = "--<<-"
[[iosevka.compLig]]
unicode = 57727 # 0xe17f
featureTag = 'XALL'
sequence = "<<<-"
[[iosevka.compLig]]
unicode = 57728 # 0xe180
featureTag = 'XALL'
sequence = "-<<<-"
[[iosevka.compLig]]
unicode = 57729 # 0xe181
featureTag = 'XALL'
sequence = "--<<<-"
[[iosevka.compLig]]
unicode = 57730 # 0xe182
featureTag = 'XALL'
sequence = "<--"
[[iosevka.compLig]]
unicode = 57731 # 0xe183
featureTag = 'XALL'
sequence = "-<--"
[[iosevka.compLig]]
unicode = 57732 # 0xe184
featureTag = 'XALL'
sequence = "--<--"
[[iosevka.compLig]]
unicode = 57733 # 0xe185
featureTag = 'XALL'
sequence = "<<--"
[[iosevka.compLig]]
unicode = 57734 # 0xe186
featureTag = 'XALL'
sequence = "-<<--"
[[iosevka.compLig]]
unicode = 57735 # 0xe187
featureTag = 'XALL'
sequence = "--<<--"
[[iosevka.compLig]]
unicode = 57736 # 0xe188
featureTag = 'XALL'
sequence = "<<<--"
[[iosevka.compLig]]
unicode = 57737 # 0xe189
featureTag = 'XALL'
sequence = "-<<<--"
[[iosevka.compLig]]
unicode = 57738 # 0xe18a
featureTag = 'XALL'
sequence = "--<<<--"
[[iosevka.compLig]]
unicode = 57739 # 0xe18b
featureTag = 'XALL'
sequence = "-<"
[[iosevka.compLig]]
unicode = 57740 # 0xe18c
featureTag = 'XALL'
sequence = "--<"
[[iosevka.compLig]]
unicode = 57741 # 0xe18d
featureTag = 'XALL'
sequence = "-<<"
[[iosevka.compLig]]
unicode = 57742 # 0xe18e
featureTag = 'XALL'
sequence = "--<<"
[[iosevka.compLig]]
unicode = 57743 # 0xe18f
featureTag = 'XALL'
sequence = "-<<<"
[[iosevka.compLig]]
unicode = 57744 # 0xe190
featureTag = 'XALL'
sequence = "--<<<"
[[iosevka.compLig]]
unicode = 57745 # 0xe191
featureTag = 'XALL'
sequence = "<="
[[iosevka.compLig]]
unicode = 57746 # 0xe192
featureTag = 'XALL'
sequence = "=<="
[[iosevka.compLig]]
unicode = 57747 # 0xe193
featureTag = 'XALL'
sequence = "==<="
[[iosevka.compLig]]
unicode = 57748 # 0xe194
featureTag = 'XALL'
sequence = "<<="
[[iosevka.compLig]]
unicode = 57749 # 0xe195
featureTag = 'XALL'
sequence = "=<<="
[[iosevka.compLig]]
unicode = 57750 # 0xe196
featureTag = 'XALL'
sequence = "==<<="
[[iosevka.compLig]]
unicode = 57751 # 0xe197
featureTag = 'XALL'
sequence = "<<<="
[[iosevka.compLig]]
unicode = 57752 # 0xe198
featureTag = 'XALL'
sequence = "=<<<="
[[iosevka.compLig]]
unicode = 57753 # 0xe199
featureTag = 'XALL'
sequence = "==<<<="
[[iosevka.compLig]]
unicode = 57754 # 0xe19a
featureTag = 'XALL'
sequence = "<=="
[[iosevka.compLig]]
unicode = 57755 # 0xe19b
featureTag = 'XALL'
sequence = "=<=="
[[iosevka.compLig]]
unicode = 57756 # 0xe19c
featureTag = 'XALL'
sequence = "==<=="
[[iosevka.compLig]]
unicode = 57757 # 0xe19d
featureTag = 'XALL'
sequence = "<<=="
[[iosevka.compLig]]
unicode = 57758 # 0xe19e
featureTag = 'XALL'
sequence = "=<<=="
[[iosevka.compLig]]
unicode = 57759 # 0xe19f
featureTag = 'XALL'
sequence = "==<<=="
[[iosevka.compLig]]
unicode = 57760 # 0xe1a0
featureTag = 'XALL'
sequence = "<<<=="
[[iosevka.compLig]]
unicode = 57761 # 0xe1a1
featureTag = 'XALL'
sequence = "=<<<=="
[[iosevka.compLig]]
unicode = 57762 # 0xe1a2
featureTag = 'XALL'
sequence = "==<<<=="
[[iosevka.compLig]]
unicode = 57763 # 0xe1a3
featureTag = 'XALL'
sequence = "=<"
[[iosevka.compLig]]
unicode = 57764 # 0xe1a4
featureTag = 'XALL'
sequence = "==<"
[[iosevka.compLig]]
unicode = 57765 # 0xe1a5
featureTag = 'XALL'
sequence = "=<<"
[[iosevka.compLig]]
unicode = 57766 # 0xe1a6
featureTag = 'XALL'
sequence = "==<<"
[[iosevka.compLig]]
unicode = 57767 # 0xe1a7
featureTag = 'XALL'
sequence = "=<<<"
[[iosevka.compLig]]
unicode = 57768 # 0xe1a8
featureTag = 'XALL'
sequence = "==<<<"
# -----------------------------------------
# Monadic operators
# -----------------------------------------
[[iosevka.compLig]]
unicode = 57769 # 0xe1a9
featureTag = 'XALL'
sequence = ">=>"
[[iosevka.compLig]]
unicode = 57770 # 0xe1aa
featureTag = 'XALL'
sequence = ">->"
[[iosevka.compLig]]
unicode = 57771 # 0xe1ab
featureTag = 'XALL'
sequence = ">-->"
[[iosevka.compLig]]
unicode = 57772 # 0xe1ac
featureTag = 'XALL'
sequence = ">==>"
[[iosevka.compLig]]
unicode = 57773 # 0xe1ad
featureTag = 'XALL'
sequence = "<=<"
[[iosevka.compLig]]
unicode = 57774 # 0xe1ae
featureTag = 'XALL'
sequence = "<-<"
[[iosevka.compLig]]
unicode = 57775 # 0xe1af
featureTag = 'XALL'
sequence = "<--<"
[[iosevka.compLig]]
unicode = 57776 # 0xe1b0
featureTag = 'XALL'
sequence = "<==<"
# -----------------------------------------
# Composition operators
# -----------------------------------------
[[iosevka.compLig]]
unicode = 57777 # 0xe1b1
featureTag = 'XALL'
sequence = ">>"
[[iosevka.compLig]]
unicode = 57778 # 0xe1b2
featureTag = 'XALL'
sequence = ">>>"
[[iosevka.compLig]]
unicode = 57779 # 0xe1b3
featureTag = 'XALL'
sequence = "<<"
[[iosevka.compLig]]
unicode = 57780 # 0xe1b4
featureTag = 'XALL'
sequence = "<<<"
# -----------------------------------------
# Lens operators
# -----------------------------------------
[[iosevka.compLig]]
unicode = 57781 # 0xe1b5
featureTag = 'XALL'
sequence = ":+"
[[iosevka.compLig]]
unicode = 57782 # 0xe1b6
featureTag = 'XALL'
sequence = ":-"
[[iosevka.compLig]]
unicode = 57783 # 0xe1b7
featureTag = 'XALL'
sequence = ":="
[[iosevka.compLig]]
unicode = 57784 # 0xe1b8
featureTag = 'XALL'
sequence = "+:"
[[iosevka.compLig]]
unicode = 57785 # 0xe1b9
featureTag = 'XALL'
sequence = "-:"
[[iosevka.compLig]]
unicode = 57786 # 0xe1ba
featureTag = 'XALL'
sequence = "=:"
[[iosevka.compLig]]
unicode = 57787 # 0xe1bb
featureTag = 'XALL'
sequence = "=^"
[[iosevka.compLig]]
unicode = 57788 # 0xe1bc
featureTag = 'XALL'
sequence = "=+"
[[iosevka.compLig]]
unicode = 57789 # 0xe1bd
featureTag = 'XALL'
sequence = "=-"
[[iosevka.compLig]]
unicode = 57790 # 0xe1be
featureTag = 'XALL'
sequence = "=*"
[[iosevka.compLig]]
unicode = 57791 # 0xe1bf
featureTag = 'XALL'
sequence = "=/"
[[iosevka.compLig]]
unicode = 57792 # 0xe1c0
featureTag = 'XALL'
sequence = "=%"
[[iosevka.compLig]]
unicode = 57793 # 0xe1c1
featureTag = 'XALL'
sequence = "^="
[[iosevka.compLig]]
unicode = 57794 # 0xe1c2
featureTag = 'XALL'
sequence = "+="
[[iosevka.compLig]]
unicode = 57795 # 0xe1c3
featureTag = 'XALL'
sequence = "-="
[[iosevka.compLig]]
unicode = 57796 # 0xe1c4
featureTag = 'XALL'
sequence = "*="
[[iosevka.compLig]]
unicode = 57797 # 0xe1c5
featureTag = 'XALL'
sequence = "/="
[[iosevka.compLig]]
unicode = 57798 # 0xe1c6
featureTag = 'XALL'
sequence = "%="
# -----------------------------------------
# Logical
# -----------------------------------------
[[iosevka.compLig]]
unicode = 57799 # 0xe1c7
featureTag = 'XALL'
sequence = "/\\"
[[iosevka.compLig]]
unicode = 57800 # 0xe1c8
featureTag = 'XALL'
sequence = "\\/"
# -----------------------------------------
# Semigroup/monoid operators
# -----------------------------------------
[[iosevka.compLig]]
unicode = 57801 # 0xe1c9
featureTag = 'XALL'
sequence = "<>"
[[iosevka.compLig]]
unicode = 57802 # 0xe1ca
featureTag = 'XALL'
sequence = "<+"
[[iosevka.compLig]]
unicode = 57803 # 0xe1cb
featureTag = 'XALL'
sequence = "<+>"
[[iosevka.compLig]]
unicode = 57804 # 0xe1cc
featureTag = 'XALL'
sequence = "+>"
[[iosevka.compLig]]
unicode = 57805 # 0xe1cc
featureTag = 'XALL'
sequence = ">~>"
[[iosevka.compLig]]
unicode = 57806 # 0xe1cc
featureTag = 'XALL'
sequence = "<~>"
;; I use Spacemacs, so I put this in user-config
;; Note that the script above only generates the long list of pairs.
;; The surrounding code is stolen from the PragmataPro scripts floating around on Gist.
(setq prettify-symbols-unprettify-at-point 'right-edge)
(defun setup-iosevka-ligatures ()
(setq prettify-symbols-alist
(append prettify-symbols-alist '(
;; Double-ended hyphen arrows ----------------
("<->" . #Xe100)
("<-->" . #Xe101)
("<--->" . #Xe102)
("<---->" . #Xe103)
("<----->" . #Xe104)
;; Double-ended equals arrows ----------------
("<=>" . #Xe105)
("<==>" . #Xe106)
("<===>" . #Xe107)
("<====>" . #Xe108)
("<=====>" . #Xe109)
;; Double-ended asterisk operators ----------------
("<**>" . #Xe10a)
("<***>" . #Xe10b)
("<****>" . #Xe10c)
("<*****>" . #Xe10d)
;; HTML comments ----------------
("<!--" . #Xe10e)
("<!---" . #Xe10f)
;; Three-char ops with discards ----------------
("<$" . #Xe110)
("<$>" . #Xe111)
("$>" . #Xe112)
("<." . #Xe113)
("<.>" . #Xe114)
(".>" . #Xe115)
("<*" . #Xe116)
("<*>" . #Xe117)
("*>" . #Xe118)
("<\\" . #Xe119)
("<\\>" . #Xe11a)
("\\>" . #Xe11b)
("</" . #Xe11c)
("</>" . #Xe11d)
("/>" . #Xe11e)
("<\"" . #Xe11f)
("<\">" . #Xe120)
("\">" . #Xe121)
("<'" . #Xe122)
("<'>" . #Xe123)
("'>" . #Xe124)
("<^" . #Xe125)
("<^>" . #Xe126)
("^>" . #Xe127)
("<&" . #Xe128)
("<&>" . #Xe129)
("&>" . #Xe12a)
("<%" . #Xe12b)
("<%>" . #Xe12c)
("%>" . #Xe12d)
("<@" . #Xe12e)
("<@>" . #Xe12f)
("@>" . #Xe130)
("<#" . #Xe131)
("<#>" . #Xe132)
("#>" . #Xe133)
("<+" . #Xe134)
("<+>" . #Xe135)
("+>" . #Xe136)
("<-" . #Xe137)
("<->" . #Xe138)
("->" . #Xe139)
("<!" . #Xe13a)
("<!>" . #Xe13b)
("!>" . #Xe13c)
("<?" . #Xe13d)
("<?>" . #Xe13e)
("?>" . #Xe13f)
("<|" . #Xe140)
("<|>" . #Xe141)
("|>" . #Xe142)
("<:" . #Xe143)
("<:>" . #Xe144)
(":>" . #Xe145)
;; Colons ----------------
("::" . #Xe146)
(":::" . #Xe147)
("::::" . #Xe148)
;; Arrow-like operators ----------------
("->" . #Xe149)
("->-" . #Xe14a)
("->--" . #Xe14b)
("->>" . #Xe14c)
("->>-" . #Xe14d)
("->>--" . #Xe14e)
("->>>" . #Xe14f)
("->>>-" . #Xe150)
("->>>--" . #Xe151)
("-->" . #Xe152)
("-->-" . #Xe153)
("-->--" . #Xe154)
("-->>" . #Xe155)
("-->>-" . #Xe156)
("-->>--" . #Xe157)
("-->>>" . #Xe158)
("-->>>-" . #Xe159)
("-->>>--" . #Xe15a)
(">-" . #Xe15b)
(">--" . #Xe15c)
(">>-" . #Xe15d)
(">>--" . #Xe15e)
(">>>-" . #Xe15f)
(">>>--" . #Xe160)
("=>" . #Xe161)
("=>=" . #Xe162)
("=>==" . #Xe163)
("=>>" . #Xe164)
("=>>=" . #Xe165)
("=>>==" . #Xe166)
("=>>>" . #Xe167)
("=>>>=" . #Xe168)
("=>>>==" . #Xe169)
("==>" . #Xe16a)
("==>=" . #Xe16b)
("==>==" . #Xe16c)
("==>>" . #Xe16d)
("==>>=" . #Xe16e)
("==>>==" . #Xe16f)
("==>>>" . #Xe170)
("==>>>=" . #Xe171)
("==>>>==" . #Xe172)
(">=" . #Xe173)
(">==" . #Xe174)
(">>=" . #Xe175)
(">>==" . #Xe176)
(">>>=" . #Xe177)
(">>>==" . #Xe178)
("<-" . #Xe179)
("-<-" . #Xe17a)
("--<-" . #Xe17b)
("<<-" . #Xe17c)
("-<<-" . #Xe17d)
("--<<-" . #Xe17e)
("<<<-" . #Xe17f)
("-<<<-" . #Xe180)
("--<<<-" . #Xe181)
("<--" . #Xe182)
("-<--" . #Xe183)
("--<--" . #Xe184)
("<<--" . #Xe185)
("-<<--" . #Xe186)
("--<<--" . #Xe187)
("<<<--" . #Xe188)
("-<<<--" . #Xe189)
("--<<<--" . #Xe18a)
("-<" . #Xe18b)
("--<" . #Xe18c)
("-<<" . #Xe18d)
("--<<" . #Xe18e)
("-<<<" . #Xe18f)
("--<<<" . #Xe190)
("<=" . #Xe191)
("=<=" . #Xe192)
("==<=" . #Xe193)
("<<=" . #Xe194)
("=<<=" . #Xe195)
("==<<=" . #Xe196)
("<<<=" . #Xe197)
("=<<<=" . #Xe198)
("==<<<=" . #Xe199)
("<==" . #Xe19a)
("=<==" . #Xe19b)
("==<==" . #Xe19c)
("<<==" . #Xe19d)
("=<<==" . #Xe19e)
("==<<==" . #Xe19f)
("<<<==" . #Xe1a0)
("=<<<==" . #Xe1a1)
("==<<<==" . #Xe1a2)
("=<" . #Xe1a3)
("==<" . #Xe1a4)
("=<<" . #Xe1a5)
("==<<" . #Xe1a6)
("=<<<" . #Xe1a7)
("==<<<" . #Xe1a8)
;; Monadic operators ----------------
(">=>" . #Xe1a9)
(">->" . #Xe1aa)
(">-->" . #Xe1ab)
(">==>" . #Xe1ac)
("<=<" . #Xe1ad)
("<-<" . #Xe1ae)
("<--<" . #Xe1af)
("<==<" . #Xe1b0)
;; Composition operators ----------------
(">>" . #Xe1b1)
(">>>" . #Xe1b2)
("<<" . #Xe1b3)
("<<<" . #Xe1b4)
;; Lens operators ----------------
(":+" . #Xe1b5)
(":-" . #Xe1b6)
(":=" . #Xe1b7)
("+:" . #Xe1b8)
("-:" . #Xe1b9)
("=:" . #Xe1ba)
("=^" . #Xe1bb)
("=+" . #Xe1bc)
("=-" . #Xe1bd)
("=*" . #Xe1be)
("=/" . #Xe1bf)
("=%" . #Xe1c0)
("^=" . #Xe1c1)
("+=" . #Xe1c2)
("-=" . #Xe1c3)
("*=" . #Xe1c4)
("/=" . #Xe1c5)
("%=" . #Xe1c6)
;; Logical ----------------
("/\\" . #Xe1c7)
("\\/" . #Xe1c8)
;; Semigroup/monoid operators ----------------
("<>" . #Xe1c9)
("<+" . #Xe1ca)
("<+>" . #Xe1cb)
("+>" . #Xe1cc)
))))
(defun refresh-pretty ()
(prettify-symbols-mode -1)
(prettify-symbols-mode +1))
;; Hooks for modes in which to install the Iosevka ligatures
(mapc (lambda (hook)
(add-hook hook (lambda () (setup-iosevka-ligatures) (refresh-pretty))))
'(text-mode-hook
prog-mode-hook))
(global-prettify-symbols-mode +1)
@fmthoma
Copy link

fmthoma commented Apr 15, 2017

@sykora Unless your're building this with @mrkgnao's fork of iosevka, the XALL won't work. I just replaced XALL with XHS0 (since I'm going to use the ligations mainly with Haskell). You don't need any additional build parameters, just append the toToml output to your parameters.toml and make custom-config && make custom.

The XALL/XHS0 tells the build system which feature tag to use when rendering the ligature. So, for example, if you replace the featureTag = 'XALL' with featureTag = 'calt' for the >>= ligature, it will render as a single glyph of the three ordinary characters, since calt does not define a ligation for >>=. On the other hand, with featureTag = 'XHS0', it will render as a single glyph of the contextual alternative characters, AKA the actual ligation (since the feature tag XHS0 defines a ligation for >>=).

@mustaqimM
Copy link

Hey there, @fmthoma. I appended the parameters.toml above to my parameters.toml and have my private-build-plans.toml set as:

[buildPlans.iosevka-custom]                  # <iosevka-custom> is your plan name
family = "Iosevka"                           # Font menu family name
design = ["termlig", "ligset-custom", "powerline-scale-y-1500", "powerline-scale-x-1500", "v-y-curly", "v-l-tailed", "v-i-hooky", "v-g-opendoublestorey", "v-zero-dotted", "v-asterisk-low", "v-dollar-opencap", "v-numbersign-slanted", "v-underscore-low"]

In parameters.toml I tried [ligset-custom] defLigSet = "XALL" . And even subbing XALL with XV00. But all ligatures are mixed up when used with Doom Emac's pretty code. What am I doing wrong?

@peschkaj
Copy link

peschkaj commented Sep 4, 2019

@mustaqimM - I believe have run into the same problems that you have. When I build Iosevka v2.3.0 with custom ligatures, I run into problems where the hex codes in the original script don't match up with the character codes in the actual font:

image

:: is being rendered as an Arabic symbol and -> is being rendered as an underscore.

@mustaqimM
Copy link

@peschkaj Try it again with the dev branch,

image

Also parameters.toml shouldn't be touched, rather add it now to private-build-plans.toml:

[[buildPlans.iosevka-custom.compatibility-ligatures]]
unicode = 57657 # 0xE139
featureTag = 'calt'
sequence = '->'

The problem was the glyphs weren't being added to the font during compilation. You can see if it was added: on linux with GNOME Unicode Charmap

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment