boon/cheat-sheet.hs

229 lines
7.3 KiB
Haskell
Raw Normal View History

2016-08-27 21:46:23 +02:00
{-# OPTIONS_GHC -XTypeSynonymInstances -XOverloadedStrings -XRecursiveDo -pgmF marxup -F #-}
2014-10-18 23:16:06 +02:00
{-# LANGUAGE TupleSections #-}
import Data.Char (toUpper)
2016-08-27 21:46:23 +02:00
import Prelude hiding (mapM,sequence,Num(..),(/))
2014-10-18 23:16:06 +02:00
import MarXup
import MarXup.Latex
2016-08-27 21:46:23 +02:00
import MarXup.Tex hiding (label)
2014-10-18 23:16:06 +02:00
import Control.Applicative
import Data.Monoid
import Control.Monad (unless)
2016-08-27 21:46:23 +02:00
import Graphics.Diagrams
2014-10-18 23:16:06 +02:00
import MarXup.Diagram
import MarXup.Latex.Math (ensureMath)
import Control.Lens (set)
-- import Data.String
import Data.Traversable
2016-08-27 21:53:11 +02:00
import Data.List (zip4,zipWith4,isSuffixOf,isPrefixOf)
2016-08-27 21:46:23 +02:00
import Algebra.Classes
2014-10-18 23:16:06 +02:00
preamble body = do
documentClass "article" ["10pt"]
usepackage "fontspec" []
cmd "setsansfont" (tex "DejaVu Sans")
cmd "setmainfont" (tex "DejaVu Serif")
usepackage "tikz" []
usepackage "graphicx" []
usepackage "amssymb" []
usepackage "varwidth" []
2014-10-24 21:04:58 +02:00
usepackage "geometry" ["margin=1cm","paper=a4paper","landscape"]
2014-10-18 23:16:06 +02:00
env "document" body
leftHandK = [["q","w","f","p","g"]
,["a","r","s","t","d"]
,["z","x","c","v","b"]]
2014-11-06 13:07:52 +01:00
rightHandK = [["j","l","u","y",";"," "]
2014-10-18 23:16:06 +02:00
,["h","n","e","i","o","'"]
,["k","m",",",".","/"," "]]
upKey c = case [c] of
"'" -> head "\""
"," -> '<'
"." -> '>'
"/" -> '?'
_ -> toUpper c
data Argument = Bin Argument Argument | None | Char | SearchObject | TextRegion | Prefix | Enclosure | Reserved
argColor :: Argument -> String
argColor a = case a of
None -> "gray"
Char -> "red"
SearchObject -> "orange"
Prefix -> "yellow"
TextRegion -> "blue"
Bin _ _ -> "purple"
_ -> "white"
reserved :: (TeX,Argument)
reserved = (italic "reserved",Reserved)
leftHandM = [["Quote", "backWard", "Forward", "Pursue", "Gather"]
,["Around", "Replace", "Splice", "Take", "Displace"]
,["", "eXtended", "Command", "⋎ (insert mark)", "Bank"]
]
leftHandL = [[("escape",Char), ("search backward",SearchObject), ("search forward",SearchObject), ("helm-occur",None), ("helm-...",Prefix)]
,[("enclose",Bin Enclosure TextRegion), ("kill+insert", TextRegion), ("yank", None), ("kill", TextRegion), ("replace char", Char)]
,[reserved, ("C-x",Prefix), ("C-c C-...",Prefix), ("insert mode",None), ("yank register",Char)]
]
leftHandR = [[("quotes (string)",None), ("word",None), ("word",None), ("paragraph",None), reserved]
2016-08-27 21:53:11 +02:00
,[("enclosure",TextRegion), ("whole-line",None), ("symbol",None), reserved, ("document",None), ("previous-region",None)]
2014-10-18 23:16:06 +02:00
,[("inclosure",TextRegion), ("s-expr",None), ("s-expr contents",None), reserved, reserved]
]
leftHandU = [[reserved, ("re-search backward",None), ("re-search forward",None), ("Play-macro",None), reserved]
,[reserved, ("Record macro", None), ("pop-yank", None), ("copy", TextRegion), reserved]
,[reserved, reserved, reserved, ("open line",None), ("copy register",Char)]
]
moveC :: String -> (TeX,Argument)
moveC "" = ("",Reserved)
2016-08-27 21:53:11 +02:00
moveC x | "avy" `isPrefixOf` x = (textual x,Char)
2014-10-18 23:16:06 +02:00
moveC x | "region" `isSuffixOf` x = (textual x,TextRegion)
moveC x = (textual x,None)
movesC = map (map moveC)
rightHandL = movesC
2016-08-27 21:46:23 +02:00
[["jump-to-def", "begin-of-line", "previous-line", "next-line", "end-of-line"]
2016-08-27 21:53:11 +02:00
,["avy-jump", "smarter-left", "backward-char", "forward-char", "smarter-right", "toggle mark-active"]
2014-10-18 23:16:06 +02:00
,["pop-mark", "", "begin-of-expr", "end-of-expr", ""]
]
rightHandU = movesC
2016-08-27 21:46:23 +02:00
[["reserved", "", "previous-paragraph", "next-paragraph", ""]
2016-08-28 08:16:40 +02:00
,["avy-jump-char", "", "smarter-up", "smarter-down", "", ""]
2016-08-27 21:46:23 +02:00
,["pop-mark-quick", "", "begin-of-buffer", "end-of-buffer", ""]
2014-10-18 23:16:06 +02:00
]
sm = cmd0 "shortmid"
ma = ensureMath
rightHandM = [["Jump", "", "", "", ""]
,["Hop", "" , "", "", "" , "'"]
,["bacK to marK", "", "", "", ""]
]
varwidth x body = env "varwidth" ((braces $ tex x) >> cmd0 "centering" >> body)
zzip = zipWith zip
zzipWith = zipWith . zipWith
zzip4 f = zipWith4 (zipWith4 f)
zzip3 f = zipWith3 (zipWith3 f)
keySize :: Constant
keySize = 65
fontsize :: String -> String -> TeX -> TeX
fontsize x y body = braces $ cmdn_ "fontsize" [tex x, tex y] <> body
2016-08-27 21:46:23 +02:00
-- keyHalf :: String -> (TeX,Argument) -> TexDiagram Anchorage
2014-10-18 23:16:06 +02:00
keyHalf k (act,arg) = do
2016-08-27 21:46:23 +02:00
up <- using (fill (argColor arg)) $ draw $ box "keyHalf"
upK <- label "k" $ textSize Huge $ sans $ textual $ k
upT <- label "scr" $ varwidth "45pt" $ sans $ textSize ScriptSize $ act
2014-10-18 23:16:06 +02:00
up # E .=. upT # E
up # W .=. upK # W
width up === constant keySize
height up === constant (keySize / 2)
return up
2016-08-27 21:46:23 +02:00
2014-10-18 23:16:06 +02:00
keyDiagram k mnem l u = do
2016-08-27 21:46:23 +02:00
b <- using (set lineWidth thick) $ draw $ box "keyB"
2014-10-18 23:16:06 +02:00
up <- keyHalf (map upKey k) u
down <- keyHalf k l
2016-08-27 21:46:23 +02:00
m <- (label "mnem" $ sans $ textSize Tiny $ mnem)
2014-10-18 23:16:06 +02:00
m # SW .=. b # SW
up # S .=. down # N
b # NW .=. up # NW
b # NE .=. up # NE
b # SE .=. down # SE
return b
2016-08-27 21:46:23 +02:00
keyFull :: Constant -> String -> TeX -> Argument -> TexDiagram Object
2014-10-18 23:16:06 +02:00
keyFull w k act arg = do
2016-08-27 21:46:23 +02:00
b <- using (set lineWidth thick . fill (argColor arg)) $ draw $ box "kf"
2014-10-18 23:16:06 +02:00
width b === constant w
height b === constant keySize
2016-08-27 21:46:23 +02:00
k' <- label "huge" $ textSize Huge $ textual $ k
act' <- label "scr2" $ varwidth "55pt" $ sans $ textSize ScriptSize $ act
2014-10-18 23:16:06 +02:00
k' # NW .=. b # NW
act' # S .=. b # S
return b
keyDist :: Constant
keyDist = 5
2014-10-24 21:04:58 +02:00
argDescs =
[(Bin Enclosure TextRegion, "First an enclosure, then a region")
,(None,"No Argument")
,(Char,"A character")
,(SearchObject,"A search space")
,(TextRegion,"A region")
,(Prefix,"(Prefix map)")
2014-10-24 22:40:05 +02:00
-- ,(Enclosure,"An enclosure")
2014-10-24 21:04:58 +02:00
,(Reserved,"(Reserved key)")]
2016-08-27 21:46:23 +02:00
legend :: TexDiagram ()
2014-10-24 21:04:58 +02:00
legend = do
2016-08-27 21:46:23 +02:00
txt <- label "legleg" (textSize Tiny $ "Color corresponds to the type of expected argument:")
2014-10-24 21:04:58 +02:00
ds <- forM argDescs $
\ (arg,desc) -> do
2016-08-27 21:46:23 +02:00
b <- using (set lineWidth thick . fill (argColor arg)) $ draw $ box "legend"
2014-10-24 21:04:58 +02:00
width b === constant 15
height b === constant 15
2016-08-27 21:46:23 +02:00
l <- label "desc" desc
2014-10-24 21:04:58 +02:00
b # E .=. l # W
return b
2016-08-27 21:46:23 +02:00
let ds' = ds++[txt]
align xpart (map (# W) ds')
spread vdist (constant 5) ds'
2014-10-24 21:04:58 +02:00
2016-08-27 21:46:23 +02:00
matrixDiag :: [[TexDiagram Object]] -> TexDiagram [[Object]]
2014-10-18 23:16:06 +02:00
matrixDiag matrix = do
keys <- mapM sequence $ reverse $ matrix
spread hdist (constant keyDist) $ (keys !! 1)
spread vdist (constant keyDist) $ map head keys
alignMatrix $ map (map (# Center)) keys
return $ reverse keys
keyBDiag = do
keys <- matrixDiag (zzip4 keyDiagram (leftHandK +++ rightHandK) (leftHandM +++ rightHandM) (leftHandL +++ rightHandL) (leftHandU +++ rightHandU))
esc <- keyFull keySize "esc" "back to normal mode" None
2016-08-27 21:46:23 +02:00
esc # SW .=. (keys !! 0 !! 0) # NW + (Point zero (constant keyDist))
2014-10-18 23:16:06 +02:00
bar <- keyFull (keySize * 6 + keyDist * 5) "space" "select region" TextRegion
2016-08-27 21:46:23 +02:00
keys !! 2 !! 2 # SW .=. bar # NW + (Point zero (constant keyDist))
2014-10-18 23:16:06 +02:00
return ()
regDiag = do
2016-08-27 21:46:23 +02:00
txt <- label "lhtrs" "Left-hand text region specifiers:"
2014-10-18 23:16:06 +02:00
keys <- matrixDiag (zzipWith keyHalf leftHandK leftHandR)
2016-08-27 21:46:23 +02:00
spread vdist (constant 7) [keys!!0!!0,txt]
2014-10-18 23:16:06 +02:00
return ()
(+++) :: [[a]] -> [[a]] -> [[a]]
x +++ y = zipWith (++) x y
2016-08-27 21:46:23 +02:00
main = renderTex Plain "cheat-sheet" docu
2014-10-18 23:16:06 +02:00
docu :: TeX
docu = preamble «
2014-10-30 22:22:34 +01:00
BOON cheat sheet. It is recommended to read the TUTORIAL to make sense of this. The color of a key indicates the type of argument it expects.
2014-10-18 23:16:06 +02:00
2014-10-30 22:22:34 +01:00
Command mode bindings.
2014-10-24 21:04:58 +02:00
@keyBDiag
2014-10-18 23:16:06 +02:00
2014-10-24 22:40:05 +02:00
@vspace"1em"
2016-08-27 21:46:23 +02:00
@regDiag
@hfill
@legend
2014-10-18 23:16:06 +02:00
»