Skip to content

Instantly share code, notes, and snippets.

@lshifr
Created February 4, 2012 20:12
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save lshifr/1739837 to your computer and use it in GitHub Desktop.
Save lshifr/1739837 to your computer and use it in GitHub Desktop.
Code highligher generator
(* Mathematica Package *)
(* Created by the Wolfram Workbench 05.01.2012 *)
BeginPackage["CodeHighlighterGenerator`"]
(* Exported symbols added here with SymbolName::usage *)
HighlighterLocation;
HighlighterPackageName;
SymbolNames;
UpdateOnLetterKeyPressed;
Types;
TokenizerOptions;
HighlightingTokenFunctionGenerator;
FunctionNames;
CachingOptions;
SaveToFile;
MakeHighlighterPackage;
Begin["`Private`"]
(* Implementation of the package *)
MakeHighlighterPackage::interr = "Internal error in function `1`, called with arguments `2`";
throwError[f_,args___] :=
Throw[$Failed, error[f,{args}]];
error[f_] :=
f[args___] :=
throwError[f,args];
ClearAll[handleError];
SetAttributes[handleError, HoldAll];
handleError[code_] :=
Catch[code, _error,
Function[{value, tag},
Message[MakeHighlighterPackage::interr, Style[First@tag, Red], Style[Last@tag,Blue]];
value
]];
ClearAll[optionQ, mergeOptions];
optionQ[opt_] :=
MatchQ[opt, _Rule | _RuleDelayed];
mergeOptions[x_, y_] :=
mergeOptions[Null, x, y];
mergeOptions[x_, y_, x_] :=
y
mergeOptions[x_, fopt_?optionQ, sopts_] :=
mergeOptions[x, {fopt}, sopts];
mergeOptions[x_, fopts_, sopt_?optionQ] :=
mergeOptions[x, fopts, {sopt}];
mergeOptions[_, fopts : {___?optionQ}, sopts : {___?optionQ}] :=
Map[# -> mergeOptions[#, # /. fopts, # /. sopts] &, fopts[[All, 1]]];
mergeOptions[_, x_, y_] :=
y;
ClearAll[makeTypeFunction];
makeTypeFunction[typeF_Symbol, types_List, typeElemsHash_] :=
Join @@ Append[
Flatten[
Map[
Function[type,
Append[
Map[Hold[typeF[type][#] = True] &, typeElemsHash[type]],
Hold[typeF[type][_] = False]
]],
types]
],
Hold[typeF[_][_] = False]];
error[makeTypeFunction];
ClearAll[makeTokenizer];
makeTokenizer[tokenizeF_Symbol, typeElemsHash_,
tokenizerOptions : {___?OptionQ}] :=
With[ {tokenizer = "Tokenizer" /. tokenizerOptions,
cacheQ = "CacheTokenizer" /. tokenizerOptions},
If[ tokenizer =!= Automatic,
If[ cacheQ,
Hold[
tokenizeF[code_String] :=
tokenizeF[code] = tokenizer[code]],
(* else *)
Hold[tokenizeF[code_String] :=
tokenizer[code]]
],
(* else *)
With[ {autoTokOpts =
"AutomaticTokenizerOptions" /. tokenizerOptions},
With[ {tokenPattern =
Apply[Alternatives,
"TokenizingOrder" /. autoTokOpts /. autoTokOpts /.
("ExplicitTypes" -> tps_) :>
Sequence @@
Reverse[
SortBy[Flatten[Map[typeElemsHash, tps]], StringLength]]
]},
If[ cacheQ,
Hold[
tokenizeF[code_String] :=
tokenizeF[code] =
DeleteCases[StringSplit[code, tok : tokenPattern :> tok],
""]],
(* else*)
Hold[
tokenizeF[code_String] :=
DeleteCases[StringSplit[code, tok : tokenPattern :> tok],
""]]
]
]
]
]
];
error[makeTokenizer];
ClearAll[makeHighlighter];
Options[makeHighlighter] = {
Types -> {
"Keywords" -> {"Color" -> RGBColor[0.5, 0, 0.5],
"FontWeight" -> Bold, "Elements" -> {}},
"Operators" -> {"Color" -> RGBColor[0, 0, 0.5],
"FontWeight" -> Bold, "Elements" -> {}},
"Builtins" -> {"Color" -> RGBColor[1, 0, 1],
"FontWeight" -> Bold, "Elements" -> {}},
"Brackets" -> {"Color" -> RGBColor[0.5, 03, 0],
"FontWeight" -> Bold, "Elements" -> {"[", "]"}},
"Parens" -> {"Color" -> GrayLevel[0.5], "FontWeight" -> Bold,
"Elements" -> {"(", ")"}},
"Braces" -> {"Color" -> RGBColor[0.4, 0, 0],
"FontWeight" -> Bold, "Elements" -> {"{", "}"}},
"Numbers" -> {"Color" -> RGBColor[0, 0, 1],
"FontWeight" -> Plain,
"Elements" -> {x_String /; StringMatchQ[x, NumberString]}} ,
"Strings" -> {"Color" -> GrayLevel[0.5], "FontWeight" -> Bold,
"Elements" -> {x_String /;
StringMatchQ[x, "\"" ~~ ___ ~~ "\""]}}
},
TokenizerOptions -> {
"Tokenizer" -> Automatic,
"AutomaticTokenizerOptions" -> {
"LiteralPattern" -> ((WordCharacter | "_") ..),
"StringPattern" -> ShortestMatch["\"" ~~ ___ ~~ "\""],
"NumberPattern" -> NumberString,
"TokenizingOrder" -> {
"StringPattern",
"NumberPattern",
"LiteralPattern",
"ExplicitTypes" -> {"Brackets", "Parens", "Braces",
"Operators"}}
}
},
HighlightingTokenFunctionGenerator ->
Function[rules,
(StyleBox[#, FontWeight -> "FontWeight",
FontColor -> "Color"] &) /. rules],
FunctionNames -> {
"Tokenizer" :> Symbol["tokenize"],
"TypeChecker" :> Symbol["typeQ"],
"Highlighter" :> Symbol["highlight"]
},
CachingOptions -> {
"CacheTokenSets" -> True,
"CacheIndividualTokens" -> True,
"CacheTokenizer" -> True
}
};
makeHighlighter[opts___?optionQ] :=
Module[ {elems, ov, typeFunctionCode, highlighterCode, setd},
With[ {merged = mergeOptions[Options[makeHighlighter], {opts}]},
ov[x_] :=
x /. merged;
];
With[ {
typeOpts = ov[Types],
types = ov[Types][[All, 1]],
hgen = ov[HighlightingTokenFunctionGenerator],
tokenOpts = ov[TokenizerOptions],
tokenize = "Tokenizer" /. ov[FunctionNames],
typeQ = "TypeChecker" /. ov[FunctionNames],
highlight = "Highlighter" /. ov[FunctionNames],
tokenSetCaching = "CacheTokenSets" /. ov[CachingOptions],
tokenCaching = "CacheIndividualTokens" /. ov[CachingOptions],
tokenizerCaching = "CacheTokenizer" /. ov[CachingOptions]
},
(* Initialization *)
Map[(elems[#] = "Elements" /. (# /. typeOpts)) &, types];
typeFunctionCode = makeTypeFunction[typeQ, types, elems];
(* Building the highlighter *)
highlighterCode = Join @@ Join[
If[ TrueQ@tokenSetCaching,
{Hold[
setd[highlight[tokens_List],
highlight[tokens] = Map[highlight, tokens]]]},
(* else *)
{Hold[setd[highlight[tokens_List], Map[highlight, tokens]]]}
],
Map[
With[ {hfun = hgen[ # /. typeOpts]},
If[ TrueQ@tokenCaching,
Hold[setd[highlight[PatternTest[x_, typeQ[#]]],
highlight[x] = hfun[x]]],
(* else *)
Hold[setd[highlight[PatternTest[x_, typeQ[#]]], hfun[x]]]
]
] &,
types
],
If[ TrueQ@tokenCaching,
{Hold[setd[highlight[tok_], highlight[tok] = tok]]},
(* else *)
{Hold[setd[highlight[tok_], tok]]}
]
] /. setd :> SetDelayed;
{
typeFunctionCode,
highlighterCode,
makeTokenizer[tokenize, elems,
Append[tokenOpts, "CacheTokenizer" -> tokenizerCaching] ]
}
]
];
error[makeHighlighter];
ClearAll[bracketMatchingCode];
bracketMatchingCode[] :=
{
Hold[
positionByStringPosition[tokens_, pos_Integer] :=
If[ # =!= {},
#[[1, 1]],
#
] &@
Position[Accumulate[StringLength /@ tokens], pos]
],
Hold[
forwardMatch[tokens_, tpos_Integer, del : ("(" | "[" | "{")] :=
Module[ {i = 0,
revdel = del /. {"(" -> ")", "[" -> "]", "{" -> "}"}},
If[ Length[#] == 2,
#[[2, 1]] + tpos - 1,
{}
] &@
Position[tokens[[tpos ;;]] /. {del :> i++, revdel :> --i}, 0,
1, 2]
]
],
Hold[
backwardMatch[tokens_, tpos_Integer, revdel : (")" | "]" | "}")] :=
Module[ {i = 0,
del = revdel /. {")" -> "(", "]" -> "[", "}" -> "{"}},
If[ Length[#] >= 2,
#[[-2, 1]],
{}
] &@
Position[Reverse[Reverse[tokens[[1 ;; tpos]]] /.
{revdel :> i++, del :> --i}], 0, 1]
]
],
(* TODO Make memoization here optional*)
Hold[
bracketMatchHighlight[tokens_, pos_] :=
(* bracketMatchHighlight[tokens, pos] = *)
Module[ {toks = tokens, match = {},
tpos = positionByStringPosition[tokens, pos]},
If[ tpos =!= {},
If[ MemberQ[{"(", "[", "{"}, toks[[tpos]]],
match = forwardMatch[toks, tpos, toks[[tpos]]]
];
If[ MemberQ[{")", "]", "}"}, toks[[tpos]]],
match = backwardMatch[toks, tpos, toks[[tpos]]]
]
];
If[ match =!= {},
toks[[{tpos, match}]] =
Map[
StyleBox[#, FontWeight -> Bold,
FontColor -> RGBColor[1, 0.5, 0]] &,
toks[[{tpos, match}]]
]
];
toks
]
]
};
ClearAll[keyActionCode]
keyActionCode[] :=
Hold[
keyAction[transformRuleFunction_, relativePosMove_Integer,
actions_] :=
Module[ {nb, cp, a},
nb = EvaluationNotebook[];
SetOptions[NotebookSelection[nb], ShowSelection -> False];
cp = "CursorPosition" /. Developer`CellInformation[nb];
SelectionMove[nb, All, ButtonCell, AutoScroll -> False];
SetOptions[NotebookSelection[nb], ShowSelection -> False];
a = NotebookRead[nb];
NotebookWrite[nb, (a /. transformRuleFunction[cp[[1, 1]]]), All,
AutoScroll -> False];
SetOptions[NotebookSelection[nb], ShowSelection -> False];
SelectionMove[nb, Previous, Cell, AutoScroll -> False];
SelectionMove[nb, After, Cell, AutoScroll -> False];
SelectionMove[nb, After, CellContents, AutoScroll -> False];
SetOptions[NotebookSelection[nb],
CellEventActions -> actions,
GeneratedCell -> True,
CellAutoOverwrite -> True,
ShowSelection -> False
];
With[ {sel = NotebookSelection[nb]},
SelectionMove[nb, All, CellContents, AutoScroll -> False];
SelectionMove[nb, Previous, Character, AutoScroll -> False];
Do[SelectionMove[nb, Next, Character,
AutoScroll -> False], {cp[[1, 1]] + relativePosMove}];
SetOptions[sel, ShowSelection -> True]
]
]
];
ClearAll[mouseActionCode]
mouseActionCode[] :=
Hold[
mouseAction[] :=
Module[ {nb},
nb = EvaluationNotebook[];
SelectionMove[nb, All, ButtonCell];
SetOptions[NotebookSelection[nb], ShowSelection -> True];
]
]
ClearAll[cellHighlightRuleCode]
cellHighlightRuleCode[] :=
Hold[
cellHighlightRule[postprocessF_] :=
Cell[body : _, "Program", rest : ___] :>
Cell[
TextData[
postprocessF@StringJoin@Cases[body, _String, {0, Infinity}]
],
"Program",
rest]];
ClearAll[processQuotesCode];
processQuotesCode[] :=
Hold[
processQuotes[text_String] :=
StringReplace[text, {FromCharacterCode[8220] :> "\"", FromCharacterCode[8221] :> "\""}]
];
ClearAll[makeHighlightF];
makeHighlightF[highlightF_Symbol, opts : OptionsPattern[]] :=
Module[ {fnames =
OptionValue[makeHighlighter, {opts}, FunctionNames] },
ClearAll[highlightF];
With[ {highlight = "Highlighter" /. fnames,
tokenize = "Tokenizer" /. fnames},
Hold[highlightF[pos_Integer] :=
highlight@bracketMatchHighlight[#, pos] &@
tokenize@processQuotes@# &
]
]
]
error[makeHighlightF];
ClearAll[makeCharacterEnterHighlightF];
makeCharacterEnterHighlightF[characterEnterHighlightF_Symbol,
highlightF_Symbol] :=
Module[ {},
ClearAll[characterEnterHighlightF];
Hold[characterEnterHighlightF[char_String, pos_Integer] :=
highlightF[pos]@StringInsert[#, char, pos] &@# &
]
];
error[makeCharacterEnterHighlightF];
ClearAll[makeActions];
Options[makeActions] = {
UpdateOnLetterKeyPressed -> False,
Sequence @@ Options[makeHighlighter]
};
makeActions[actions_Symbol, highlightF_Symbol,
characterEnterHighlightF_Symbol, opts : OptionsPattern[]] :=
Module[ {},
ClearAll[actions];
With[ {keyEvents =
If[ TrueQ@OptionValue[UpdateOnLetterKeyPressed],
Sequence @@ Map[
{"KeyDown", #} :>
keyAction[
Function[{pos},
cellHighlightRule[characterEnterHighlightF[#, pos + 1]]],
1, actions] &,
Join[CharacterRange["a", "z"], {FromCharacterCode[8220],FromCharacterCode[8221], "\""}]],
(* else *)
Sequence @@ {}
]},
Hold[actions =
{"LeftArrowKeyDown" :>
keyAction[
Function[{pos}, cellHighlightRule[highlightF[pos]]], -1,
actions],
"RightArrowKeyDown" :>
keyAction[
Function[{pos}, cellHighlightRule[highlightF[pos + 1]]], 1,
actions],
"MouseOver" :> mouseAction[],
{"KeyDown", " "} :>
keyAction[
Function[{pos},
cellHighlightRule[characterEnterHighlightF[" ", pos + 1]]],
1, actions],
keyEvents
}]
]
];
error[makeActions];
ClearAll[makeCodeCell];
makeCodeCell[getCellF_Symbol, actions_, opts___?OptionQ] :=
With[ { copts = Sequence @@ FilterRules[{opts},
ParseTimeNameSpaceWrapper[Options[Cell],LocalizingContext->"Global`"]
] },
{
Hold[Options[getCellF] = {"InitialText"->"Enter code here"}],
Hold[getCellF[options___?OptionQ] :=
With[ {text = "InitialText"/.Flatten[{options}]/.Options[getCellF]},
Cell[
TextData[{text}],
"Program",
CellEventActions -> actions,
Sequence @@ Flatten[{options}],
copts
]
]
]
}
];
error[makeCodeCell];
ClearAll[newlineSymbol];
newlineSymbol[] :=
newline;
ClearAll[joinCode];
joinCode[pieces : {__Hold}, newlineSymbol_: newlineSymbol[]] :=
Replace[#, Hold[sts___] :> Hold[ce[sts]]] &@
Apply[Join, #] &@Riffle[#, Hold[newlineSymbol]] &@pieces;
error[joinCode];
ClearAll[ce, package, inContext];
ce[sts___] :=
CompoundExpression[sts];
package[name_, code_] :=
(BeginPackage[name];
code;
EndPackage[]);
inContext[name_, code_] :=
(Begin[name];
code;
End[]);
ClearAll[expansionRules];
expansionRules[heads : {__Symbol}] :=
Flatten[DownValues /@ heads]
error[expansionRules];
allHeadsToExpand[] :=
{package, inContext, ce}
Clear[generateCode];
(* generateCode[code:{__Hold}]:=generateCode@joinCode[code]; *)
generateCode[code_Hold] :=
code //. expansionRules[allHeadsToExpand[]] //.
HoldPattern[
CompoundExpression[left___,
CompoundExpression[middle___],
right___]] :> (left;
middle;
right);
error[generateCode];
Clear[formatCode];
formatCode[code_Hold, newlineSymbol_: newlineSymbol[]] :=
With[ {newline = StringJoin[ToString@newlineSymbol, ";"]},
StringReplace[
Function[cd, ToString[Unevaluated[cd], InputForm], HoldAll] @@
code,
{newline :> "\n\n", "/;" :> "/;", ";;" :> ";;", ";" :> ";\n"}]
];
error[formatCode];
ClearAll[makePackage];
makePackage[context_String, publicCode_Hold, privateCode : {__Hold},
newlineSymbol_: newlineSymbol[]] :=
Module[ {myHold},
SetAttributes[myHold, HoldAll];
With[ {
pcd = myHold @@ joinCode[{publicCode}, newlineSymbol],
prcd = myHold @@ joinCode[privateCode, newlineSymbol]
},
Hold[
package[context,
ce[
pcd,
inContext["`Private`",
ce[newlineSymbol, prcd, newlineSymbol]
]
]]]
] /. myHold[x__] :> x
]
error[makePackage];
ClearAll[makeHighlighterPackageBody];
Options[makeHighlighterPackageBody] = {
SymbolNames :> {
"HighlightFunction" :> Symbol["HighlightFunction"],
"CharacterEnterHighlightFunction" :>
Symbol["CharacterEnterHighlightFunction"],
"EventActions" :> Symbol["EventActions"],
"CellGenerator" :> Symbol["GetCell"]
},
Sequence @@ Options[makeActions]
};
makeHighlighterPackageBody[opts : OptionsPattern[]] :=
Module[ {ov},
With[ {merged =
mergeOptions[Options[makeHighlighterPackageBody], {opts}]},
ov[x_] :=
x /. merged
];
With[ {names = ov[SymbolNames]},
With[ {
highlightFunction = "HighlightFunction" /. names,
characterEnterHighlightFunction =
"CharacterEnterHighlightFunction" /. names,
actions = "EventActions" /. names,
getCellFunction = "CellGenerator" /. names
},
Join[
makeHighlighter[
Sequence @@ FilterRules[{opts}, Options[makeHighlighter]]],
bracketMatchingCode[],
Flatten@{
keyActionCode[],
mouseActionCode[],
cellHighlightRuleCode[],
processQuotesCode[],
makeHighlightF[highlightFunction],
makeCharacterEnterHighlightF[characterEnterHighlightFunction,
highlightFunction],
makeActions[
actions,
highlightFunction,
characterEnterHighlightFunction,
Sequence @@ FilterRules[{opts}, Options[makeActions]]],
makeCodeCell[getCellFunction, actions]
}
]
]
]
];
error[makeHighlighterPackageBody];
ClearAll[makeHighlighterPackageCode];
Options[makeHighlighterPackageCode] = {
NewlineSymbol :> Automatic ,
Sequence @@ Options[makeHighlighterPackageBody]
};
makeHighlighterPackageCode[context_String, opts___?OptionQ] :=
Module[ {ov},
With[ {merged =
mergeOptions[Options[makeHighlighterPackageCode], {opts}]},
ov[x_] :=
x /. merged
];
With[ {
newlineSymbol =
If[ # === Automatic,
newlineSymbol[],
#
] &@ov[NewlineSymbol],
cellMakingFunctionName = "CellGenerator" /. ov[SymbolNames]
},
generateCode[
makePackage[
context,
Hold[ce[newlineSymbol, cellMakingFunctionName, newlineSymbol]],
makeHighlighterPackageBody[opts]
]]
]
];
error[makeHighlighterPackageCode];
Clear[saveCode];
saveCode[file_String, generatedCode_] :=
With[ {result =
BinaryWrite[file, formatCode@generatedCode, "TerminatedString"]},
Close[file];
result
];
error[saveCode];
ClearAll[ParseTimeNameSpaceWrapper];
SetAttributes[ParseTimeNameSpaceWrapper, HoldFirst];
Options[ParseTimeNameSpaceWrapper] =
{
LocalizingContext -> "MyLocalizingContext`",
DefaultImportedContexts :> {},
ExtraImportedContexts :> {}
};
ParseTimeNameSpaceWrapper[code_, opts : OptionsPattern[]] :=
Module[ {result, context = OptionValue[LocalizingContext],
defcontexts = OptionValue[DefaultImportedContexts],
extraContexts = OptionValue[ExtraImportedContexts],
allContexts},
allContexts = {Sequence @@ defcontexts, Sequence @@ extraContexts};
BeginPackage[context,
If[ allContexts === {},
Sequence @@ {},
allContexts
]];
result = handleError@code;
Block[ {$ContextPath },
EndPackage[]
];
result
];
Clear[MakeHighlighterPackage];
Options[MakeHighlighterPackage] = {
HighlighterLocation :>
FileNameJoin[
Append[FileNameSplit[$UserBaseDirectory], "Applications"]],
HighlighterPackageName :> Automatic,
Sequence @@ Options[makeHighlighterPackageCode],
SaveToFile -> True
};
With[ {defcontext = $Context},
MakeHighlighterPackage[
context_String /; StringMatchQ[context, __ ~~ "`"],
opts : OptionsPattern[]] :=
Module[ {packageCode, localizingContext = "MyWorkingContext`",merged},
Block[ {$Packages = Append[$Packages,defcontext],$ContextPath = $ContextPath, $Context = $Context},
ParseTimeNameSpaceWrapper[
merged = mergeOptions[Options[MakeHighlighterPackage], {opts}];
packageCode =
makeHighlighterPackageCode[context,
Sequence@@FilterRules[merged,Options[makeHighlighterPackageCode]]];
If[ TrueQ[OptionValue[SaveToFile]],
With[ {fileName =
FileNameJoin[
Join[
FileNameSplit[OptionValue[HighlighterLocation]],
FileNameSplit[
If[ OptionValue[HighlighterPackageName] === Automatic,
ContextToFileName[context],
(* else *)
OptionValue[HighlighterPackageName]
]]]]},
saveCode[fileName, packageCode]
]
];
Remove @@ {localizingContext <> "*"};
packageCode,
LocalizingContext -> localizingContext,
ExtraImportedContexts -> {defcontext}
]
]
]
];
End[]
EndPackage[]
(* Content-type: application/vnd.wolfram.mathematica *)
(*** Wolfram Notebook File ***)
(* http://www.wolfram.com/nb *)
(* CreatedBy='Mathematica 8.0' *)
(*CacheID: 234*)
(* Internal cache information:
NotebookFileLineBreakTest
NotebookFileLineBreakTest
NotebookDataPosition[ 157, 7]
NotebookDataLength[ 67447, 2012]
NotebookOptionsPosition[ 62978, 1865]
NotebookOutlinePosition[ 63618, 1890]
CellTagsIndexPosition[ 63532, 1885]
WindowFrame->Normal*)
(* Beginning of Notebook Content *)
Notebook[{
Cell[CellGroupData[{
Cell["\<\
\t\t\tCode highlighter package generator\
\>", "Subtitle",
CellChangeTimes->{{3.5347843797001953`*^9, 3.534784393138672*^9}}],
Cell[CellGroupData[{
Cell["\<\
An example: code highlighter for C\
\>", "Section",
CellChangeTimes->{{3.534780379479492*^9, 3.5347803914414062`*^9}},
FontWeight->"Plain"],
Cell[BoxData[""], "Input",
CellChangeTimes->{{3.537372279536133*^9, 3.5373722808164062`*^9}}],
Cell[BoxData[
RowBox[{"Needs", "[", "\"\<CodeHighlighterGenerator`\>\"", "]"}]], "Input",
CellChangeTimes->{{3.537372242504883*^9, 3.5373722705634766`*^9},
3.5373734948066406`*^9}],
Cell[CellGroupData[{
Cell["\<\
Making a simple code highlighter for C\
\>", "Subsection",
CellChangeTimes->{{3.5347804186523438`*^9, 3.534780432198242*^9}},
FontWeight->"Plain"],
Cell[TextData[{
"This creates a simple code highlighter for C, covering some (but not all) \
standard library functions, ",
StyleBox["and not covering the preprocessor macros",
FontWeight->"Bold"]
}], "Text",
CellChangeTimes->{{3.5347815606484375`*^9, 3.5347816087753906`*^9}}],
Cell["\<\
This code below will generate a full package containing the code highlighting \
functionality (for C language in this example), and save it to a specified \
location. The default location is at $UserBaseDirectory/Applications.\
\>", "Text",
CellChangeTimes->{{3.5347606760683594`*^9, 3.5347607408183594`*^9},
3.5373747064697266`*^9}],
Cell[BoxData[
RowBox[{
RowBox[{"MakeHighlighterPackage", "[",
RowBox[{"\"\<CCodeHighlighter`\>\"", ",", "\[IndentingNewLine]",
RowBox[{"Types", "\[Rule]",
RowBox[{"{", "\[IndentingNewLine]",
RowBox[{
RowBox[{"\"\<Operators\>\"", "\[Rule]", " ",
RowBox[{"\"\<Elements\>\"", "\[Rule]", " ",
RowBox[{"{",
RowBox[{
"\"\<=\>\"", ",", "\"\<[\>\"", ",", "\"\<]\>\"", ",", "\"\<:\>\"",
",", "\"\<&&\>\"", ",", "\"\<||\>\"", ",", "\"\<&\>\"", ",",
"\"\<|\>\"", ",", "\"\<==\>\"", ",", "\"\<<=\>\"", ",",
"\"\<>=\>\"", ",", "\"\<!=\>\"", ",", "\"\<!\>\"", ",",
"\"\<>\>\"", ",", "\"\<<\>\"", ",", "\"\<+\>\"", ",", "\"\<-\>\"",
",", "\"\<*\>\"", ",", "\"\</\>\"", ",", "\"\<++\>\"", ",",
"\"\<--\>\"", ",", "\"\<->\>\"", ",", "\"\<.\>\"", ",",
"\"\<;\>\"", ",", "\"\<:\>\""}], "}"}]}]}], ",",
"\[IndentingNewLine]",
RowBox[{"\"\<Builtins\>\"", "\[Rule]",
RowBox[{"\"\<Elements\>\"", "\[Rule]", " ",
RowBox[{"{",
RowBox[{
"\"\<memchr\>\"", ",", "\"\<memcmp\>\"", ",", "\"\<memcpy\>\"",
",", "\"\<memmove\>\"", ",", "\"\<memset\>\"", ",",
"\"\<strcat\>\"", ",", "\"\<strchr\>\"", ",", "\"\<strcmp\>\"",
",", "\"\<strcoll\>\"", ",", "\"\<strcpy\>\"", ",",
"\"\<strcspn\>\"", ",", "\"\<strerror\>\"", ",", "\"\<strlen\>\"",
",", "\"\<strncat\>\"", ",", "\"\<strncmp\>\"", ",",
"\"\<strncpy\>\"", ",", "\"\<strpbrk\>\"", ",", "\"\<strrchr\>\"",
",", "\"\<strspn\>\"", ",", "\"\<strstr\>\"", ",",
"\"\<strtok\>\"", ",", "\"\<strxfrm\>\"", ",", "\"\<clearerr\>\"",
",", "\"\<fclose\>\"", ",", "\"\<feof\>\"", ",", "\"\<ferror\>\"",
",", "\"\<fflush\>\"", ",", "\"\<fgetc\>\"", ",",
"\"\<fgetpos\>\"", ",", "\"\<fgets\>\"", ",", "\"\<fopen\>\"",
",", "\"\<fprintf\>\"", ",", "\"\<fputc\>\"", ",", "\"\<fputs\>\"",
",", "\"\<fread\>\"", ",", "\"\<freopen\>\"", ",",
"\"\<fscanf\>\"", ",", "\"\<fseek\>\"", ",", "\"\<fsetpos\>\"",
",", "\"\<ftell\>\"", ",", "\"\<fwrite\>\"", ",", "\"\<getc\>\"",
",", "\"\<getchar\>\"", ",", "\"\<gets\>\"", ",", "\"\<perror\>\"",
",", "\"\<printf\>\"", ",", "\"\<putc\>\"", ",",
"\"\<putchar\>\"", ",", "\"\<puts\>\"", ",", "\"\<remove\>\"",
",", "\"\<rename\>\"", ",", "\"\<rewind\>\"", ",", "\"\<scanf\>\"",
",", "\"\<setbuf\>\"", ",", "\"\<setvbuf\>\"", ",",
"\"\<sprintf\>\"", ",", "\"\<sscanf\>\"", ",", "\"\<tmpfile\>\"",
",", "\"\<tmpnam\>\"", ",", "\"\<ungetc\>\"", ",",
"\"\<vfprintf\>\"", ",", "\"\<vprintf\>\"", ",",
"\"\<vsprintf\>\"", ",", "\"\<abort\>\"", ",", "\"\<abs\>\"", ",",
"\"\<atexit\>\"", ",", "\"\<atof\>\"", ",", "\"\<atoi\>\"", ",",
"\"\<atol\>\"", ",", "\"\<bsearch\>\"", ",", "\"\<calloc\>\"",
",", "\"\<div\>\"", ",", "\"\<exit\>\"", ",", "\"\<free\>\"", ",",
"\"\<getenv\>\"", ",", "\"\<labs\>\"", ",", "\"\<ldiv\>\"", ",",
"\"\<malloc\>\"", ",", "\"\<mblen\>\"", ",", "\"\<mbstowcs\>\"",
",", "\"\<mbtowc\>\"", ",", "\"\<qsort\>\"", ",", "\"\<rand\>\"",
",", "\"\<realloc\>\"", ",", "\"\<srand\>\"", ",",
"\"\<strtod\>\"", ",", "\"\<strtol\>\"", ",", "\"\<strtoul\>\"",
",", "\"\<system\>\"", ",", "\"\<wcstombs\>\"", ",",
"\"\<wctomb\>\"", ",", "\"\<itoa\>\""}], "}"}]}]}], ",",
"\[IndentingNewLine]",
RowBox[{"\"\<Keywords\>\"", "\[Rule]",
RowBox[{"\"\<Elements\>\"", "\[Rule]",
RowBox[{"{",
RowBox[{
"\"\<auto\>\"", ",", "\"\<break\>\"", ",", "\"\<case\>\"", ",",
"\"\<char\>\"", ",", "\"\<const\>\"", ",", "\"\<continue\>\"",
",", "\"\<default\>\"", ",", "\"\<do\>\"", ",", "\"\<double\>\"",
",", "\"\<else\>\"", ",", "\"\<enum\>\"", ",", "\"\<extern\>\"",
",", "\"\<float\>\"", ",", "\"\<for\>\"", ",", "\"\<goto\>\"",
",", "\"\<if\>\"", ",", "\"\<int\>\"", ",", "\"\<long\>\"", ",",
"\"\<register\>\"", ",", "\"\<return\>\"", ",", "\"\<short\>\"",
",", "\"\<signed\>\"", ",", "\"\<sizeof\>\"", ",",
"\"\<static\>\"", ",", "\"\<struct\>\"", ",", "\"\<switch\>\"",
",", "\"\<typedef\>\"", ",", "\"\<union\>\"", ",",
"\"\<unsigned\>\"", ",", "\"\<void\>\"", ",", "\"\<volatile\>\"",
",", "\"\<while\>\""}], "}"}]}]}]}], "}"}]}], ",",
"\[IndentingNewLine]",
RowBox[{"SymbolNames", "\[RuleDelayed]",
RowBox[{"{", "\[IndentingNewLine]",
RowBox[{
RowBox[{"\"\<CellGenerator\>\"", "\[RuleDelayed]",
RowBox[{"Symbol", "[", "\"\<GetCCell\>\"", "]"}]}], ",",
"\[IndentingNewLine]",
RowBox[{
"\"\<EventActions\>\"", "\[RuleDelayed]", " ", "cEventActions"}]}],
"\[IndentingNewLine]", "}"}]}]}], "\[IndentingNewLine]", "]"}],
";"}]], "Input",
CellChangeTimes->{
3.5347803006445312`*^9, {3.5347803410195312`*^9, 3.5347803691367188`*^9},
3.5347815527089844`*^9}],
Cell["\<\
The result of this code running is the full parsed code of the resulting \
package. It was suppressed here by a semicolon at the end.\
\>", "Text",
CellChangeTimes->{{3.534775200486328*^9, 3.5347752616777344`*^9}}],
Cell[CellGroupData[{
Cell["Notes", "Subsubsection",
CellChangeTimes->{{3.534757641411133*^9, 3.534757643631836*^9},
3.534784314604492*^9}],
Cell[TextData[{
"1. The lexical analyzer (tokenizer) for the highlighter is generated \
automatically, based on the option settings, particularly ",
StyleBox["TokenizerOptions",
FontSlant->"Italic"],
" and ",
StyleBox["Types->Operators",
FontSlant->"Italic"],
". \nOne can instead supply a user-defined tokenizer through the \
TokenizerOptions\[Rule]\[CloseCurlyDoubleQuote]Tokenizer\
\[CloseCurlyDoubleQuote] option.\n2. The two main things that makes sense to \
expose to the user are:\n\t- The symbol where we store the event actions \
(here we used a symbol ",
StyleBox["Global`cEventActions",
FontWeight->"Bold",
FontSlant->"Italic",
FontColor->RGBColor[0.5, 0, 0.5]],
"). It is is not indicated, a default symbol is generated for it, but not \
exported.\n\t- The function to generate a cell in the \
\[OpenCurlyDoubleQuote]Program\[CloseCurlyDoubleQuote] style, taking possible \
Cell style options, with the event actions handler embedded in it. This is a \
higher-level option. Here we indicated that we want it to have a short name ",
StyleBox["GetCCell",
FontWeight->"Bold",
FontSlant->"Italic",
FontColor->RGBColor[0.5, 0, 0.5]],
" , and to reside in the public context of our package (here ",
StyleBox["CCodeHighlighter` ",
FontWeight->"Bold",
FontSlant->"Italic",
FontColor->RGBColor[0.5, 0, 0.5]],
"). We could have used any other symbol we want."
}], "Text",
CellChangeTimes->{{3.5347576472910156`*^9, 3.53475779915625*^9}, {
3.534760516180664*^9, 3.5347606475722656`*^9}, {3.534760756879883*^9,
3.534760800203125*^9}, {3.534776152944336*^9, 3.5347763565009766`*^9}, {
3.537373616069336*^9, 3.537373641126953*^9}}]
}, Open ]],
Cell[CellGroupData[{
Cell["The generated package location and contents", "Subsubsection",
CellChangeTimes->{{3.5347609491904297`*^9, 3.534760957870117*^9}}],
Cell["Check that we have the file generated:", "Text",
CellChangeTimes->{{3.5347608120429688`*^9, 3.5347608220683594`*^9}}],
Cell[CellGroupData[{
Cell[BoxData[
RowBox[{"FindFile", "[", "\"\<CCodeHighlighter.m\>\"", "]"}]], "Input",
CellChangeTimes->{{3.5373736731416016`*^9, 3.5373736734003906`*^9}}],
Cell[BoxData["\<\"C:\\\\Users\\\\Archie\\\\AppData\\\\Roaming\\\\Mathematica\\\
\\Applications\\\\CCodeHighlighter.m\"\>"], "Output",
CellChangeTimes->{
3.5347571541376953`*^9, 3.534758525182617*^9, 3.534776106991211*^9, {
3.534782484991211*^9, 3.534782467477539*^9}, 3.5347903146689453`*^9,
3.5347913840058594`*^9, 3.5373736738808594`*^9, 3.5373746014179688`*^9}]
}, Open ]],
Cell["Here is the text of the generated package:", "Text",
CellChangeTimes->{{3.5347609017070312`*^9, 3.5347609125771484`*^9}}],
Cell[BoxData[
RowBox[{
RowBox[{"Import", "[",
RowBox[{
RowBox[{"FindFile", "[", "\"\<CCodeHighlighter.m\>\"", "]"}], ",",
"\"\<Text\>\""}], "]"}], ";"}]], "Input",
CellChangeTimes->{{3.534760841993164*^9, 3.534760895779297*^9},
3.537374606798828*^9, {3.537374727140625*^9, 3.5373747274716797`*^9}}]
}, Open ]],
Cell[CellGroupData[{
Cell["Loading a package", "Subsubsection",
CellChangeTimes->{{3.5347777148027344`*^9, 3.5347777189921875`*^9}}],
Cell["First, we need to load the package:", "Text",
CellChangeTimes->{{3.5347610630976562`*^9, 3.5347610699003906`*^9}}],
Cell[BoxData[
RowBox[{"Needs", "[", "\"\<CCodeHighlighter`\>\"", "]"}]], "Input",
CellChangeTimes->{{3.537373679966797*^9, 3.537373680173828*^9}}]
}, Open ]],
Cell[CellGroupData[{
Cell[TextData[{
"Making code cells using ",
StyleBox["eventActions",
FontWeight->"Bold",
FontSlant->"Italic"]
}], "Subsubsection",
CellChangeTimes->{{3.5347609800009766`*^9, 3.534760993498047*^9}, {
3.534777698015625*^9, 3.5347777079492188`*^9}}],
Cell[TextData[{
"Let us inspect the ",
StyleBox["eventActions",
FontWeight->"Bold",
FontSlant->"Italic"],
" symbol, since all the functionality of the highlighter is encapsulated in \
it:"
}], "Text",
CellChangeTimes->{{3.5347612609433594`*^9, 3.5347613064716797`*^9}}],
Cell[CellGroupData[{
Cell[BoxData["cEventActions"], "Input",
CellChangeTimes->{{3.534790343720703*^9, 3.5347903444160156`*^9}, {
3.5373736888876953`*^9, 3.537373690140625*^9}}],
Cell[BoxData[
RowBox[{"{",
RowBox[{
RowBox[{"\<\"LeftArrowKeyDown\"\>", "\[RuleDelayed]",
RowBox[{"CCodeHighlighter`Private`keyAction", "[",
RowBox[{
RowBox[{"Function", "[",
RowBox[{
RowBox[{"{", "CCodeHighlighter`Private`pos$", "}"}], ",",
RowBox[{"CCodeHighlighter`Private`cellHighlightRule", "[",
RowBox[{
"CCodeHighlighter`Private`HighlightFunction", "[",
"CCodeHighlighter`Private`pos$", "]"}], "]"}]}], "]"}], ",",
RowBox[{"-", "1"}], ",", "cEventActions"}], "]"}]}], ",",
RowBox[{"\<\"RightArrowKeyDown\"\>", "\[RuleDelayed]",
RowBox[{"CCodeHighlighter`Private`keyAction", "[",
RowBox[{
RowBox[{"Function", "[",
RowBox[{
RowBox[{"{", "CCodeHighlighter`Private`pos$", "}"}], ",",
RowBox[{"CCodeHighlighter`Private`cellHighlightRule", "[",
RowBox[{"CCodeHighlighter`Private`HighlightFunction", "[",
RowBox[{"CCodeHighlighter`Private`pos$", "+", "1"}], "]"}], "]"}]}],
"]"}], ",", "1", ",", "cEventActions"}], "]"}]}], ",",
RowBox[{"\<\"MouseOver\"\>", "\[RuleDelayed]",
RowBox[{"CCodeHighlighter`Private`mouseAction", "[", "]"}]}], ",",
RowBox[{
RowBox[{"{",
RowBox[{"\<\"KeyDown\"\>", ",", "\<\" \"\>"}], "}"}], "\[RuleDelayed]",
RowBox[{"CCodeHighlighter`Private`keyAction", "[",
RowBox[{
RowBox[{"Function", "[",
RowBox[{
RowBox[{"{", "CCodeHighlighter`Private`pos$", "}"}], ",",
RowBox[{"CCodeHighlighter`Private`cellHighlightRule", "[",
RowBox[{
"CCodeHighlighter`Private`CharacterEnterHighlightFunction", "[",
RowBox[{"\<\" \"\>", ",",
RowBox[{"CCodeHighlighter`Private`pos$", "+", "1"}]}], "]"}],
"]"}]}], "]"}], ",", "1", ",", "cEventActions"}], "]"}]}]}],
"}"}]], "Output",
CellChangeTimes->{3.534761314995117*^9, 3.534776381948242*^9,
3.5347824708740234`*^9, 3.5347903450664062`*^9, 3.534790966631836*^9,
3.5347913869609375`*^9, 3.5373736908007812`*^9, 3.537374611689453*^9}]
}, Open ]],
Cell[TextData[{
"One thing to note here is that ",
StyleBox["eventActions",
FontWeight->"Bold",
FontSlant->"Italic"],
" is defined recursively, referring to itself. This is an essential feature, \
which makes it all possible."
}], "Text",
CellChangeTimes->{{3.534761342600586*^9, 3.534761396401367*^9}}],
Cell[TextData[{
"To make a code cell using the eventActions symbol, we need something like \
this (",
StyleBox["I inserted some C code into the cell, but you have to move the \
cursor with arrows or hit space, to get a highlighting",
FontSlant->"Italic",
FontColor->RGBColor[0.5, 0, 0.5]],
"):"
}], "Text",
CellChangeTimes->{{3.5347610508671875`*^9, 3.534761093830078*^9}, {
3.534776463211914*^9, 3.5347765012890625`*^9}, {3.537373702350586*^9,
3.537373702838867*^9}}],
Cell[BoxData[
RowBox[{"CellPrint", "[", "\[IndentingNewLine]",
RowBox[{"Cell", "[",
RowBox[{
RowBox[{"TextData", "[",
RowBox[{
"{", "\[IndentingNewLine]",
"\"\<int test_ordering(void){\n int testarr[MAX_ELEMS] = \
{5,1,3,7,12,4,8,9,3,10,9,7,4,2,11};\n int order[MAX_ELEMS], \
permuted[MAX_ELEMS], len = 15;\n \n \
if(find_ordering(order,testarr,len)!=0){\n printf(\\\"Error in the \
ordering function\\\\n\\\");\n return 1; \n }\n \
print_integers(order,len);\n permute(permuted,testarr,order,len);\n \
print_integers(permuted,len);\n return 0; \n}\>\"", "}"}], "]"}], ",",
"\"\<Program\>\"", ",",
RowBox[{"CellEventActions", "\[Rule]", "cEventActions"}], ",",
"\[IndentingNewLine]",
RowBox[{"Evaluatable", "\[Rule]", "True"}], ",",
RowBox[{"CellEvaluationFunction", "\[Rule]", "someCEvaluator"}], ",",
RowBox[{"CellFrameLabels", "\[Rule]",
RowBox[{"{",
RowBox[{
RowBox[{"{",
RowBox[{"None", ",", "\"\<C code\>\""}], "}"}], ",",
RowBox[{"{",
RowBox[{"None", ",", "None"}], "}"}]}], "}"}]}]}], "]"}],
"\[IndentingNewLine]", "]"}]], "Input",
CellChangeTimes->{{3.534761243270508*^9, 3.5347612461796875`*^9},
3.5347744997929688`*^9, {3.5347747537109375`*^9, 3.5347747875625*^9}, {
3.5347764413691406`*^9, 3.5347764450058594`*^9}, {3.5373737087265625`*^9,
3.537373716841797*^9}, 3.537373909379883*^9}],
Cell[TextData[{
StyleBox["int",
FontWeight->Bold,
FontColor->RGBColor[0.5, 0, 0.5]],
" ",
"test_ordering",
StyleBox["(",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
StyleBox["void",
FontWeight->Bold,
FontColor->RGBColor[0.5, 0, 0.5]],
StyleBox[")",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
StyleBox["{",
FontWeight->Bold,
FontColor->RGBColor[0.4, 0, 0]],
"\n ",
StyleBox["int",
FontWeight->Bold,
FontColor->RGBColor[0.5, 0, 0.5]],
" ",
"testarr",
StyleBox["[",
FontWeight->Bold,
FontColor->RGBColor[0, 0, 0.5]],
"MAX_ELEMS",
StyleBox["]",
FontWeight->Bold,
FontColor->RGBColor[0, 0, 0.5]],
" ",
StyleBox["=",
FontWeight->Bold,
FontColor->RGBColor[0, 0, 0.5]],
" ",
StyleBox["{",
FontWeight->Bold,
FontColor->RGBColor[0.4, 0, 0]],
StyleBox["5",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
",",
StyleBox["1",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
",",
StyleBox["3",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
",",
StyleBox["7",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
",",
StyleBox["12",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
",",
StyleBox["4",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
",",
StyleBox["8",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
",",
StyleBox["9",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
",",
StyleBox["3",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
",",
StyleBox["10",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
",",
StyleBox["9",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
",",
StyleBox["7",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
",",
StyleBox["4",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
",",
StyleBox["2",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
",",
StyleBox["11",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
StyleBox["}",
FontWeight->Bold,
FontColor->RGBColor[0.4, 0, 0]],
StyleBox[";\n",
FontWeight->Bold,
FontColor->RGBColor[0, 0, 0.5]],
" ",
StyleBox["int",
FontWeight->Bold,
FontColor->RGBColor[0.5, 0, 0.5]],
" ",
"order",
StyleBox["[",
FontWeight->Bold,
FontColor->RGBColor[0, 0, 0.5]],
"MAX_ELEMS",
StyleBox["]",
FontWeight->Bold,
FontColor->RGBColor[0, 0, 0.5]],
", ",
"permuted",
StyleBox["[",
FontWeight->Bold,
FontColor->RGBColor[0, 0, 0.5]],
"MAX_ELEMS",
StyleBox["]",
FontWeight->Bold,
FontColor->RGBColor[0, 0, 0.5]],
", ",
"len",
" ",
StyleBox["=",
FontWeight->Bold,
FontColor->RGBColor[0, 0, 0.5]],
" ",
StyleBox["15",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
StyleBox[";\n",
FontWeight->Bold,
FontColor->RGBColor[0, 0, 0.5]],
" \n ",
StyleBox["if",
FontWeight->Bold,
FontColor->RGBColor[0.5, 0, 0.5]],
StyleBox["(",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
"find_ordering",
StyleBox["(",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
"order",
",",
"testarr",
",",
"len",
StyleBox[")",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
StyleBox["!=",
FontWeight->Bold,
FontColor->RGBColor[0, 0, 0.5]],
StyleBox["0",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
StyleBox[")",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
StyleBox["{",
FontWeight->Bold,
FontColor->RGBColor[0.4, 0, 0]],
"\n ",
StyleBox["printf",
FontWeight->Bold,
FontColor->RGBColor[1, 0, 1]],
StyleBox["(",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
StyleBox["\"Error in the ordering function\\n\"",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
StyleBox[")",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
StyleBox[";\n",
FontWeight->Bold,
FontColor->RGBColor[0, 0, 0.5]],
" ",
StyleBox["return",
FontWeight->Bold,
FontColor->RGBColor[0.5, 0, 0.5]],
" ",
StyleBox["1",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
"; \n ",
StyleBox["}",
FontWeight->Bold,
FontColor->RGBColor[0.4, 0, 0]],
"\n ",
"print_integers",
StyleBox["(",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
"order",
",",
"len",
StyleBox[")",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
StyleBox[";\n",
FontWeight->Bold,
FontColor->RGBColor[0, 0, 0.5]],
" ",
"permute",
StyleBox["(",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
"permuted",
",",
"testarr",
",",
"order",
",",
"len",
StyleBox[")",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
StyleBox[";\n",
FontWeight->Bold,
FontColor->RGBColor[0, 0, 0.5]],
" ",
"print_integers",
StyleBox["(",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
"permuted",
",",
"len",
StyleBox[")",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
StyleBox[";\n",
FontWeight->Bold,
FontColor->RGBColor[0, 0, 0.5]],
" ",
StyleBox["return",
FontWeight->Bold,
FontColor->RGBColor[0.5, 0, 0.5]],
" ",
StyleBox["0",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
"; \n",
StyleBox["}",
FontWeight->Bold,
FontColor->RGBColor[0.4, 0, 0]]
}], "Program",
ShowSelection->False,
Evaluatable->True,
CellEvaluationFunction->$CellContext`someCEvaluator,
GeneratedCell->True,
CellAutoOverwrite->True,
CellEventActions->{"LeftArrowKeyDown" :> CCodeHighlighter`Private`keyAction[
Function[{CCodeHighlighter`Private`pos$},
CCodeHighlighter`Private`cellHighlightRule[
CCodeHighlighter`Private`HighlightFunction[
CCodeHighlighter`Private`pos$]]], -1, $CellContext`cEventActions],
"RightArrowKeyDown" :> CCodeHighlighter`Private`keyAction[
Function[{CCodeHighlighter`Private`pos$},
CCodeHighlighter`Private`cellHighlightRule[
CCodeHighlighter`Private`HighlightFunction[
CCodeHighlighter`Private`pos$ + 1]]], 1, $CellContext`cEventActions],
"MouseOver" :> CCodeHighlighter`Private`mouseAction[], {"KeyDown", " "} :>
CCodeHighlighter`Private`keyAction[
Function[{CCodeHighlighter`Private`pos$},
CCodeHighlighter`Private`cellHighlightRule[
CCodeHighlighter`Private`CharacterEnterHighlightFunction[
" ", CCodeHighlighter`Private`pos$ + 1]]],
1, $CellContext`cEventActions]},
CellFrameLabels->{{None, "C code"}, {None, None}},
CellChangeTimes->{3.537374614201172*^9}]
}, Open ]],
Cell[CellGroupData[{
Cell[TextData[{
"Making code cells using ",
StyleBox["GetCCell",
FontSlant->"Italic"],
" function"
}], "Subsubsection",
CellChangeTimes->{{3.5347778714033203`*^9, 3.5347778792089844`*^9}, {
3.537373937020508*^9, 3.5373739377373047`*^9}}],
Cell[TextData[{
"We can also use the somewhat higher-level function ",
StyleBox["GetCCell ",
FontWeight->"Bold",
FontSlant->"Italic"],
"to produce the code cells. The advantage of it is that the event actions \
mechanics is hidden and one does not need to indicate that explicitly."
}], "Text",
CellChangeTimes->{{3.5347778875625*^9, 3.534777980446289*^9}, {
3.5373746401503906`*^9, 3.537374640555664*^9}}],
Cell["\<\
This will create the same cell as before (again, move a cursor to highlight).\
\>", "Text",
CellChangeTimes->{{3.5347779829697266`*^9, 3.5347780245908203`*^9}}],
Cell[BoxData[
RowBox[{"CellPrint", "@",
RowBox[{"GetCCell", "[", "\[IndentingNewLine]",
RowBox[{
RowBox[{"Evaluatable", "\[Rule]", "True"}], ",", "\[IndentingNewLine]",
RowBox[{"CellEvaluationFunction", "\[Rule]", "someCEvaluator"}], ",",
"\[IndentingNewLine]",
RowBox[{"CellFrameLabels", "\[Rule]",
RowBox[{"{",
RowBox[{
RowBox[{"{",
RowBox[{"None", ",", "\"\<C code\>\""}], "}"}], ",",
RowBox[{"{",
RowBox[{"None", ",", "None"}], "}"}]}], "}"}]}], ",",
"\[IndentingNewLine]",
RowBox[{
"\"\<InitialText\>\"", "\[Rule]", " ",
"\"\<int test_ordering(void){\n int testarr[MAX_ELEMS] = \
{5,1,3,7,12,4,8,9,3,10,9,7,4,2,11};\n int order[MAX_ELEMS], \
permuted[MAX_ELEMS], len = 15;\n \n \
if(find_ordering(order,testarr,len)!=0){\n printf(\\\"Error in the \
ordering function\\\\n\\\");\n return 1; \n }\n \
print_integers(order,len);\n permute(permuted,testarr,order,len);\n \
print_integers(permuted,len);\n return 0; \n}\>\""}]}],
"]"}]}]], "Input",
CellChangeTimes->{{3.5347777742509766`*^9, 3.534777857680664*^9}, {
3.5373739411601562`*^9, 3.5373739852851562`*^9}, 3.5373747485595703`*^9}],
Cell[TextData[{
StyleBox["int",
FontWeight->Bold,
FontColor->RGBColor[0.5, 0, 0.5]],
" ",
"test_ordering",
StyleBox["(",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
StyleBox["void",
FontWeight->Bold,
FontColor->RGBColor[0.5, 0, 0.5]],
StyleBox[")",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
StyleBox["{",
FontWeight->Bold,
FontColor->RGBColor[0.4, 0, 0]],
"\n ",
StyleBox["int",
FontWeight->Bold,
FontColor->RGBColor[0.5, 0, 0.5]],
" ",
"testarr",
StyleBox["[",
FontWeight->Bold,
FontColor->RGBColor[0, 0, 0.5]],
"MAX_ELEMS",
StyleBox["]",
FontWeight->Bold,
FontColor->RGBColor[0, 0, 0.5]],
" ",
StyleBox["=",
FontWeight->Bold,
FontColor->RGBColor[0, 0, 0.5]],
" ",
StyleBox["{",
FontWeight->Bold,
FontColor->RGBColor[0.4, 0, 0]],
StyleBox["5",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
",",
StyleBox["1",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
",",
StyleBox["3",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
",",
StyleBox["7",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
",",
StyleBox["12",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
",",
StyleBox["4",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
",",
StyleBox["8",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
",",
StyleBox["9",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
",",
StyleBox["3",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
",",
StyleBox["10",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
",",
StyleBox["9",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
",",
StyleBox["7",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
",",
StyleBox["4",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
",",
StyleBox["2",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
",",
StyleBox["11",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
StyleBox["}",
FontWeight->Bold,
FontColor->RGBColor[0.4, 0, 0]],
StyleBox[";\n",
FontWeight->Bold,
FontColor->RGBColor[0, 0, 0.5]],
" ",
StyleBox["int",
FontWeight->Bold,
FontColor->RGBColor[0.5, 0, 0.5]],
" ",
"order",
StyleBox["[",
FontWeight->Bold,
FontColor->RGBColor[0, 0, 0.5]],
"MAX_ELEMS",
StyleBox["]",
FontWeight->Bold,
FontColor->RGBColor[0, 0, 0.5]],
", ",
"permuted",
StyleBox["[",
FontWeight->Bold,
FontColor->RGBColor[0, 0, 0.5]],
"MAX_ELEMS",
StyleBox["]",
FontWeight->Bold,
FontColor->RGBColor[0, 0, 0.5]],
", ",
"len",
" ",
StyleBox["=",
FontWeight->Bold,
FontColor->RGBColor[0, 0, 0.5]],
" ",
StyleBox["15",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
StyleBox[";\n",
FontWeight->Bold,
FontColor->RGBColor[0, 0, 0.5]],
" \n ",
StyleBox["if",
FontWeight->Bold,
FontColor->RGBColor[0.5, 0, 0.5]],
StyleBox["(",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
"find_ordering",
StyleBox["(",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
"order",
",",
"testarr",
",",
"len",
StyleBox[")",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
StyleBox["!=",
FontWeight->Bold,
FontColor->RGBColor[0, 0, 0.5]],
StyleBox["0",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
StyleBox[")",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
StyleBox["{",
FontWeight->Bold,
FontColor->RGBColor[0.4, 0, 0]],
"\n ",
StyleBox["printf",
FontWeight->Bold,
FontColor->RGBColor[1, 0, 1]],
StyleBox["(",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
StyleBox["\"Error in the ordering function\\n\"",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
StyleBox[")",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
StyleBox[";\n",
FontWeight->Bold,
FontColor->RGBColor[0, 0, 0.5]],
" ",
StyleBox["return",
FontWeight->Bold,
FontColor->RGBColor[0.5, 0, 0.5]],
" ",
StyleBox["1",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
"; \n ",
StyleBox["}",
FontWeight->Bold,
FontColor->RGBColor[0.4, 0, 0]],
"\n ",
"print_integers",
StyleBox["(",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
"order",
",",
"len",
StyleBox[")",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
StyleBox[";\n",
FontWeight->Bold,
FontColor->RGBColor[0, 0, 0.5]],
" ",
"permute",
StyleBox["(",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
"permuted",
",",
"testarr",
",",
"order",
",",
"len",
StyleBox[")",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
StyleBox[";\n",
FontWeight->Bold,
FontColor->RGBColor[0, 0, 0.5]],
" ",
"print_integers",
StyleBox["(",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
"permuted",
",",
"len",
StyleBox[")",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
StyleBox[";\n",
FontWeight->Bold,
FontColor->RGBColor[0, 0, 0.5]],
" ",
StyleBox["return",
FontWeight->Bold,
FontColor->RGBColor[0.5, 0, 0.5]],
" ",
StyleBox["0",
FontWeight->Plain,
FontColor->RGBColor[0, 0, 1]],
"; \n",
StyleBox["}",
FontWeight->Bold,
FontColor->RGBColor[0.4, 0, 0]]
}], "Program",
ShowSelection->False,
Evaluatable->True,
CellEvaluationFunction->$CellContext`someREvaluator,
GeneratedCell->True,
CellAutoOverwrite->True,
CellEventActions->{"LeftArrowKeyDown" :> CCodeHighlighter`Private`keyAction[
Function[{CCodeHighlighter`Private`pos$},
CCodeHighlighter`Private`cellHighlightRule[
CCodeHighlighter`Private`HighlightFunction[
CCodeHighlighter`Private`pos$]]], -1, $CellContext`cEventActions],
"RightArrowKeyDown" :> CCodeHighlighter`Private`keyAction[
Function[{CCodeHighlighter`Private`pos$},
CCodeHighlighter`Private`cellHighlightRule[
CCodeHighlighter`Private`HighlightFunction[
CCodeHighlighter`Private`pos$ + 1]]], 1, $CellContext`cEventActions],
"MouseOver" :> CCodeHighlighter`Private`mouseAction[], {"KeyDown", " "} :>
CCodeHighlighter`Private`keyAction[
Function[{CCodeHighlighter`Private`pos$},
CCodeHighlighter`Private`cellHighlightRule[
CCodeHighlighter`Private`CharacterEnterHighlightFunction[
" ", CCodeHighlighter`Private`pos$ + 1]]],
1, $CellContext`cEventActions]},
CellFrameLabels->{{None, "C code"}, {None, None}},
CellChangeTimes->{3.537374645111328*^9},
"InitialText" ->
"int test_ordering(void){\n int testarr[MAX_ELEMS] = \
{5,1,3,7,12,4,8,9,3,10,9,7,4,2,11};\n int order[MAX_ELEMS], \
permuted[MAX_ELEMS], len = 15;\n \n \
if(find_ordering(order,testarr,len)!=0){\n printf(\"Error in the \
ordering function\\n\");\n return 1; \n }\n \
print_integers(order,len);\n permute(permuted,testarr,order,len);\n \
print_integers(permuted,len);\n return 0; \n}"]
}, Open ]],
Cell[CellGroupData[{
Cell["Inspecting the internals", "Subsubsection",
CellChangeTimes->{{3.534778546265625*^9, 3.5347785517998047`*^9}}],
Cell["\<\
A number of function names for the key functions of the generated package can \
be defined by the user, and can also be inspected easily. For example, should \
we wich to inspect the code for the tokenizer, we could of course read the \
generated package code, but we can also find its short name easily:\
\>", "Text",
CellChangeTimes->{{3.5347786162226562`*^9, 3.534778699416992*^9}}],
Cell[CellGroupData[{
Cell[BoxData[
RowBox[{"FunctionNames", "/.",
RowBox[{"Options", "[", "MakeHighlighterPackage", "]"}]}]], "Input",
CellChangeTimes->{{3.5347785671748047`*^9, 3.5347786112910156`*^9}}],
Cell[BoxData[
RowBox[{"{",
RowBox[{
RowBox[{"\<\"Tokenizer\"\>", "\[RuleDelayed]",
RowBox[{"Symbol", "[", "\<\"tokenize\"\>", "]"}]}], ",",
RowBox[{"\<\"TypeChecker\"\>", "\[RuleDelayed]",
RowBox[{"Symbol", "[", "\<\"typeQ\"\>", "]"}]}], ",",
RowBox[{"\<\"Highlighter\"\>", "\[RuleDelayed]",
RowBox[{"Symbol", "[", "\<\"highlight\"\>", "]"}]}]}], "}"}]], "Output",
CellChangeTimes->{{3.5347785755166016`*^9, 3.5347786117558594`*^9},
3.534782579448242*^9, 3.534791425071289*^9, 3.537373998352539*^9,
3.537374657290039*^9}]
}, Open ]],
Cell["And therefore:", "Text",
CellChangeTimes->{{3.5347787109882812`*^9, 3.534778714463867*^9}}],
Cell[CellGroupData[{
Cell[BoxData[
RowBox[{"??", "CCodeHighlighter`Private`tokenize"}]], "Input",
CellChangeTimes->{{3.534778718520508*^9, 3.5347787434160156`*^9}, {
3.5373740030546875`*^9, 3.537374003314453*^9}}],
Cell[CellGroupData[{
Cell["CCodeHighlighter`Private`tokenize", "Print", "PrintUsage",
CellChangeTimes->{3.537374659013672*^9},
CellTags->"Info3537385458-7027350"],
Cell[BoxData[
InterpretationBox[GridBox[{
{GridBox[{
{
RowBox[{
RowBox[{
"CCodeHighlighter`Private`tokenize",
"[", "\<\"int test_ordering(void){\\n int testarr[MAX_ELEMS] = \
{5,1,3,7,12,4,8,9,3,10,9,7,4,2,11};\\n int order[MAX_ELEMS], \
permuted[MAX_ELEMS], len = 15;\\n \\n \
if(find_ordering(order,testarr,len)!=0){\\n printf(\\\"Error in the \
ordering function\\\\n\\\");\\n return 1; \\n }\\n \
print_integers(order,len);\\n permute(permuted,testarr,order,len);\\n \
print_integers(permuted,len);\\n return 0; \\n}\"\>", "]"}], "=",
RowBox[{"{",
RowBox[{"\<\"int\"\>", ",", "\<\" \"\>",
",", "\<\"test_ordering\"\>", ",", "\<\"(\"\>",
",", "\<\"void\"\>", ",", "\<\")\"\>", ",", "\<\"{\"\>",
",", "\<\"\\n \"\>", ",", "\<\"int\"\>", ",", "\<\" \"\>",
",", "\<\"testarr\"\>", ",", "\<\"[\"\>", ",", "\<\"MAX_ELEMS\"\>",
",", "\<\"]\"\>", ",", "\<\" \"\>", ",", "\<\"=\"\>",
",", "\<\" \"\>", ",", "\<\"{\"\>", ",", "\<\"5\"\>",
",", "\<\",\"\>", ",", "\<\"1\"\>", ",", "\<\",\"\>",
",", "\<\"3\"\>", ",", "\<\",\"\>", ",", "\<\"7\"\>",
",", "\<\",\"\>", ",", "\<\"12\"\>", ",", "\<\",\"\>",
",", "\<\"4\"\>", ",", "\<\",\"\>", ",", "\<\"8\"\>",
",", "\<\",\"\>", ",", "\<\"9\"\>", ",", "\<\",\"\>",
",", "\<\"3\"\>", ",", "\<\",\"\>", ",", "\<\"10\"\>",
",", "\<\",\"\>", ",", "\<\"9\"\>", ",", "\<\",\"\>",
",", "\<\"7\"\>", ",", "\<\",\"\>", ",", "\<\"4\"\>",
",", "\<\",\"\>", ",", "\<\"2\"\>", ",", "\<\",\"\>",
",", "\<\"11\"\>", ",", "\<\"}\"\>", ",", "\<\";\\n\"\>",
",", "\<\" \"\>", ",", "\<\"int\"\>", ",", "\<\" \"\>",
",", "\<\"order\"\>", ",", "\<\"[\"\>", ",", "\<\"MAX_ELEMS\"\>",
",", "\<\"]\"\>", ",", "\<\", \"\>", ",", "\<\"permuted\"\>",
",", "\<\"[\"\>", ",", "\<\"MAX_ELEMS\"\>", ",", "\<\"]\"\>",
",", "\<\", \"\>", ",", "\<\"len\"\>", ",", "\<\" \"\>",
",", "\<\"=\"\>", ",", "\<\" \"\>", ",", "\<\"15\"\>",
",", "\<\";\\n\"\>", ",", "\<\" \\n \"\>", ",", "\<\"if\"\>",
",", "\<\"(\"\>", ",", "\<\"find_ordering\"\>", ",", "\<\"(\"\>",
",", "\<\"order\"\>", ",", "\<\",\"\>", ",", "\<\"testarr\"\>",
",", "\<\",\"\>", ",", "\<\"len\"\>", ",", "\<\")\"\>",
",", "\<\"!=\"\>", ",", "\<\"0\"\>", ",", "\<\")\"\>",
",", "\<\"{\"\>", ",", "\<\"\\n \"\>",
",", "\<\"printf\"\>", ",", "\<\"(\"\>",
",", "\<\"\\\"Error in the ordering function\\\\n\\\"\"\>",
",", "\<\")\"\>", ",", "\<\";\\n\"\>", ",", "\<\" \"\>",
",", "\<\"return\"\>", ",", "\<\" \"\>", ",", "\<\"1\"\>",
",", "\<\"; \\n \"\>", ",", "\<\"}\"\>",
",", "\<\"\\n \"\>", ",", "\<\"print_integers\"\>",
",", "\<\"(\"\>", ",", "\<\"order\"\>", ",", "\<\",\"\>",
",", "\<\"len\"\>", ",", "\<\")\"\>", ",", "\<\";\\n\"\>",
",", "\<\" \"\>", ",", "\<\"permute\"\>", ",", "\<\"(\"\>",
",", "\<\"permuted\"\>", ",", "\<\",\"\>", ",", "\<\"testarr\"\>",
",", "\<\",\"\>", ",", "\<\"order\"\>", ",", "\<\",\"\>",
",", "\<\"len\"\>", ",", "\<\")\"\>", ",", "\<\";\\n\"\>",
",", "\<\" \"\>", ",", "\<\"print_integers\"\>",
",", "\<\"(\"\>", ",", "\<\"permuted\"\>", ",", "\<\",\"\>",
",", "\<\"len\"\>", ",", "\<\")\"\>", ",", "\<\";\\n\"\>",
",", "\<\" \"\>", ",", "\<\"return\"\>", ",", "\<\" \"\>",
",", "\<\"0\"\>", ",", "\<\"; \\n\"\>", ",", "\<\"}\"\>"}],
"}"}]}]},
{" "},
{
RowBox[{
RowBox[{
"CCodeHighlighter`Private`tokenize", "[",
"CCodeHighlighter`Private`code$_String", "]"}], ":=",
RowBox[{
RowBox[{
"CCodeHighlighter`Private`tokenize", "[",
"CCodeHighlighter`Private`code$", "]"}], "=",
RowBox[{"DeleteCases", "[",
RowBox[{
RowBox[{"StringSplit", "[",
RowBox[{"CCodeHighlighter`Private`code$", ",",
RowBox[{
RowBox[{"CCodeHighlighter`Private`tok", ":",
RowBox[{
RowBox[{"ShortestMatch", "[",
RowBox[{"\<\"\\\"\"\>", "~~", "___", "~~", "\<\"\\\"\"\>"}],
"]"}], "|", "NumberString", "|",
RowBox[{"(",
RowBox[{
RowBox[{"(",
RowBox[{"WordCharacter", "|", "\<\"_\"\>"}], ")"}],
".."}], ")"}], "|", "\<\">=\"\>", "|", "\<\"<=\"\>",
"|", "\<\"||\"\>", "|", "\<\"==\"\>", "|", "\<\"++\"\>",
"|", "\<\"->\"\>", "|", "\<\"--\"\>", "|", "\<\"&&\"\>",
"|", "\<\"!=\"\>", "|", "\<\":\"\>", "|", "\<\":\"\>",
"|", "\<\"/\"\>", "|", "\<\";\\n\"\>", "|", "\<\".\"\>",
"|", "\<\">\"\>", "|", "\<\"<\"\>", "|", "\<\"|\"\>",
"|", "\<\"]\"\>", "|", "\<\"]\"\>", "|", "\<\"}\"\>",
"|", "\<\"[\"\>", "|", "\<\"[\"\>", "|", "\<\"{\"\>",
"|", "\<\"=\"\>", "|", "\<\"+\"\>", "|", "\<\"-\"\>",
"|", "\<\")\"\>", "|", "\<\"(\"\>", "|", "\<\"*\"\>",
"|", "\<\"&\"\>", "|", "\<\"!\"\>"}]}], "\[RuleDelayed]",
"CCodeHighlighter`Private`tok"}]}], "]"}], ",", "\<\"\"\>"}],
"]"}]}]}]}
},
BaselinePosition->{Baseline, {1, 1}},
GridBoxAlignment->{
"Columns" -> {{Left}}, "ColumnsIndexed" -> {}, "Rows" -> {{Baseline}},
"RowsIndexed" -> {}},
GridBoxItemSize->{"Columns" -> {{
Scaled[0.999]}}, "ColumnsIndexed" -> {}, "Rows" -> {{1.}},
"RowsIndexed" -> {}}]}
},
BaselinePosition->{Baseline, {1, 1}},
GridBoxAlignment->{
"Columns" -> {{Left}}, "ColumnsIndexed" -> {}, "Rows" -> {{Baseline}},
"RowsIndexed" -> {}}],
Definition[CCodeHighlighter`Private`tokenize],
Editable->False]], "Print",
CellChangeTimes->{3.5373746590498047`*^9},
CellTags->"Info3537385458-7027350"]
}, Open ]]
}, Open ]],
Cell["We can also test this:", "Text",
CellChangeTimes->{{3.5347787515478516`*^9, 3.5347787573603516`*^9}}],
Cell[CellGroupData[{
Cell[BoxData[
RowBox[{"InputForm", "@",
RowBox[{
"CCodeHighlighter`Private`tokenize", "@",
"\"\<int test_ordering(void){\n int testarr[MAX_ELEMS] = \
{5,1,3,7,12,4,8,9,3,10,9,7,4,2,11};\n int order[MAX_ELEMS], \
permuted[MAX_ELEMS], len = 15;\n \n \
if(find_ordering(order,testarr,len)!=0){\n printf(\\\"Error in the \
ordering function\\\\n\\\");\n return 1; \n }\n \
print_integers(order,len);\n permute(permuted,testarr,order,len);\n \
print_integers(permuted,len);\n return 0; \n}\>\""}]}]], "Input",
CellChangeTimes->{{3.5347787648847656`*^9, 3.53477880034375*^9}, {
3.5373740210683594`*^9, 3.5373740409990234`*^9}}],
Cell["\<\
{\"int\", \" \", \"test_ordering\", \"(\", \"void\", \")\", \"{\", \"\\n \
\", \"int\",
\" \", \"testarr\", \"[\", \"MAX_ELEMS\", \"]\", \" \", \"=\", \" \", \"{\", \
\"5\", \",\",
\"1\", \",\", \"3\", \",\", \"7\", \",\", \"12\", \",\", \"4\", \",\", \
\"8\", \",\", \"9\",
\",\", \"3\", \",\", \"10\", \",\", \"9\", \",\", \"7\", \",\", \"4\", \
\",\", \"2\", \",\",
\"11\", \"}\", \";\\n\", \" \", \"int\", \" \", \"order\", \"[\", \
\"MAX_ELEMS\", \"]\",
\", \", \"permuted\", \"[\", \"MAX_ELEMS\", \"]\", \", \", \"len\", \" \", \
\"=\", \" \",
\"15\", \";\\n\", \" \\n \", \"if\", \"(\", \"find_ordering\", \"(\", \
\"order\",
\",\", \"testarr\", \",\", \"len\", \")\", \"!=\", \"0\", \")\", \"{\", \
\"\\n \",
\"printf\", \"(\", \"\\\"Error in the ordering function\\\\n\\\"\", \")\", \
\";\\n\",
\" \", \"return\", \" \", \"1\", \"; \\n \", \"}\", \"\\n \",
\"print_integers\", \"(\", \"order\", \",\", \"len\", \")\", \";\\n\", \" \
\",
\"permute\", \"(\", \"permuted\", \",\", \"testarr\", \",\", \"order\", \
\",\", \"len\",
\")\", \";\\n\", \" \", \"print_integers\", \"(\", \"permuted\", \",\", \
\"len\",
\")\", \";\\n\", \" \", \"return\", \" \", \"0\", \"; \\n\", \"}\"}\
\>", "Output",
CellChangeTimes->{{3.5347787864570312`*^9, 3.5347788007539062`*^9},
3.5347825890126953`*^9, 3.5347914305625*^9, 3.537374045515625*^9,
3.537374665044922*^9}]
}, Open ]],
Cell["This can be quite handy for debugging", "Text",
CellChangeTimes->{{3.5347788076103516`*^9, 3.5347788154345703`*^9}}]
}, Open ]]
}, Open ]],
Cell[CellGroupData[{
Cell["Adding caching and changing colors", "Subsection",
CellChangeTimes->{{3.534776588307617*^9, 3.5347765978623047`*^9}},
FontWeight->"Plain"],
Cell[CellGroupData[{
Cell["Options for MakeHighlighterPackage", "Subsubsection",
CellChangeTimes->{{3.5347773344726562`*^9, 3.5347773416367188`*^9}}],
Cell["\<\
To see all the options that MakeHighlighterPackage accepts, we can of course \
use this:\
\>", "Text",
CellChangeTimes->{{3.534777299830078*^9, 3.534777321991211*^9}}],
Cell[BoxData[
RowBox[{
RowBox[{"Options", "[", "MakeHighlighterPackage", "]"}], ";"}]], "Input",
CellChangeTimes->{{3.5347766247617188`*^9, 3.534776633611328*^9},
3.5347771106064453`*^9}]
}, Open ]],
Cell[CellGroupData[{
Cell["Creating an alternative highlighter", "Subsubsection",
CellChangeTimes->{{3.534777348373047*^9, 3.5347773684101562`*^9}, {
3.534778412296875*^9, 3.534778418326172*^9}}],
Cell["\<\
Here we will use a different (pretty weird but illustrative) color scheme and \
enabale caching for tokenizer and highlighter. It is not clear whether \
caching helps for smaller code cells, but it looks like it improves the \
responsiveness significantly for larger ones. \
\>", "Text",
CellChangeTimes->{{3.534777371958008*^9, 3.534777489966797*^9}}],
Cell["\<\
Note that below I've used different names for:
\t- Package context
\t- function to generate code cells
\t- symbol to store event actions\
\>", "Text",
CellChangeTimes->{{3.534777371958008*^9, 3.5347775484785156`*^9}}],
Cell["This creates the package and saves it to disk:", "Text",
CellChangeTimes->{{3.534777538234375*^9, 3.534777561788086*^9}}],
Cell[BoxData[
RowBox[{
RowBox[{"MakeHighlighterPackage", "[",
RowBox[{"\"\<CCodeHighlighterAlt`\>\"", ",", "\[IndentingNewLine]",
RowBox[{"Types", "\[Rule]",
RowBox[{"{", "\[IndentingNewLine]",
RowBox[{
RowBox[{"\"\<Operators\>\"", "\[Rule]", " ",
RowBox[{"{", "\[IndentingNewLine]",
RowBox[{
RowBox[{"\"\<Color\>\"", "\[Rule]", "Green"}], ",",
"\[IndentingNewLine]",
RowBox[{"\"\<Elements\>\"", "\[Rule]", " ",
RowBox[{"{",
RowBox[{
"\"\<:::\>\"", ",", "\"\<::\>\"", ",", "\"\<?\>\"", ",",
"\"\<$\>\"", ",", "\"\<@\>\"", ",", "\"\<<<-\>\"", ",",
"\"\<<-\>\"", ",", "\"\<->\>\"", ",", "\"\<->>\>\"", ",",
"\"\<[\>\"", ",", "\"\<]\>\"", ",", "\"\<:\>\"", ",",
"\"\<&&\>\"", ",", "\"\<||\>\"", ",", "\"\<&\>\"", ",",
"\"\<|\>\"", ",", "\"\<==\>\"", ",", "\"\<<=\>\"", ",",
"\"\<>=\>\"", ",", "\"\<!=\>\"", ",", "\"\<!\>\"", ",",
"\"\<>\>\"", ",", "\"\<<\>\"", ",", "\"\<+\>\"", ",",
"\"\<-\>\"", ",", "\"\<*\>\"", ",", "\"\</\>\""}], "}"}]}]}],
"\[IndentingNewLine]", "}"}]}], ",", "\[IndentingNewLine]",
RowBox[{"\"\<Builtins\>\"", "\[Rule]",
RowBox[{"{", "\[IndentingNewLine]",
RowBox[{
RowBox[{"\"\<Color\>\"", "\[Rule]", "Brown"}], ",",
"\[IndentingNewLine]",
RowBox[{"\"\<Elements\>\"", "\[Rule]",
RowBox[{"{",
RowBox[{
"\"\<memchr\>\"", ",", "\"\<memcmp\>\"", ",", "\"\<memcpy\>\"",
",", "\"\<memmove\>\"", ",", "\"\<memset\>\"", ",",
"\"\<strcat\>\"", ",", "\"\<strchr\>\"", ",", "\"\<strcmp\>\"",
",", "\"\<strcoll\>\"", ",", "\"\<strcpy\>\"", ",",
"\"\<strcspn\>\"", ",", "\"\<strerror\>\"", ",",
"\"\<strlen\>\"", ",", "\"\<strncat\>\"", ",", "\"\<strncmp\>\"",
",", "\"\<strncpy\>\"", ",", "\"\<strpbrk\>\"", ",",
"\"\<strrchr\>\"", ",", "\"\<strspn\>\"", ",", "\"\<strstr\>\"",
",", "\"\<strtok\>\"", ",", "\"\<strxfrm\>\"", ",",
"\"\<clearerr\>\"", ",", "\"\<fclose\>\"", ",", "\"\<feof\>\"",
",", "\"\<ferror\>\"", ",", "\"\<fflush\>\"", ",",
"\"\<fgetc\>\"", ",", "\"\<fgetpos\>\"", ",", "\"\<fgets\>\"",
",", "\"\<fopen\>\"", ",", "\"\<fprintf\>\"", ",",
"\"\<fputc\>\"", ",", "\"\<fputs\>\"", ",", "\"\<fread\>\"",
",", "\"\<freopen\>\"", ",", "\"\<fscanf\>\"", ",",
"\"\<fseek\>\"", ",", "\"\<fsetpos\>\"", ",", "\"\<ftell\>\"",
",", "\"\<fwrite\>\"", ",", "\"\<getc\>\"", ",",
"\"\<getchar\>\"", ",", "\"\<gets\>\"", ",", "\"\<perror\>\"",
",", "\"\<printf\>\"", ",", "\"\<putc\>\"", ",",
"\"\<putchar\>\"", ",", "\"\<puts\>\"", ",", "\"\<remove\>\"",
",", "\"\<rename\>\"", ",", "\"\<rewind\>\"", ",",
"\"\<scanf\>\"", ",", "\"\<setbuf\>\"", ",", "\"\<setvbuf\>\"",
",", "\"\<sprintf\>\"", ",", "\"\<sscanf\>\"", ",",
"\"\<tmpfile\>\"", ",", "\"\<tmpnam\>\"", ",", "\"\<ungetc\>\"",
",", "\"\<vfprintf\>\"", ",", "\"\<vprintf\>\"", ",",
"\"\<vsprintf\>\"", ",", "\"\<abort\>\"", ",", "\"\<abs\>\"",
",", "\"\<atexit\>\"", ",", "\"\<atof\>\"", ",", "\"\<atoi\>\"",
",", "\"\<atol\>\"", ",", "\"\<bsearch\>\"", ",",
"\"\<calloc\>\"", ",", "\"\<div\>\"", ",", "\"\<exit\>\"", ",",
"\"\<free\>\"", ",", "\"\<getenv\>\"", ",", "\"\<labs\>\"", ",",
"\"\<ldiv\>\"", ",", "\"\<malloc\>\"", ",", "\"\<mblen\>\"",
",", "\"\<mbstowcs\>\"", ",", "\"\<mbtowc\>\"", ",",
"\"\<qsort\>\"", ",", "\"\<rand\>\"", ",", "\"\<realloc\>\"",
",", "\"\<srand\>\"", ",", "\"\<strtod\>\"", ",",
"\"\<strtol\>\"", ",", "\"\<strtoul\>\"", ",", "\"\<system\>\"",
",", "\"\<wcstombs\>\"", ",", "\"\<wctomb\>\"", ",",
"\"\<itoa\>\""}], "\[IndentingNewLine]", "}"}]}]}], "}"}]}], ",",
"\[IndentingNewLine]",
RowBox[{"\"\<Keywords\>\"", "\[Rule]",
RowBox[{"{", "\[IndentingNewLine]",
RowBox[{
RowBox[{"\"\<Color\>\"", "\[Rule]", "Red"}], ",",
"\[IndentingNewLine]",
RowBox[{"\"\<Elements\>\"", "\[Rule]",
RowBox[{"{",
RowBox[{
"\"\<auto\>\"", ",", "\"\<break\>\"", ",", "\"\<case\>\"", ",",
"\"\<char\>\"", ",", "\"\<const\>\"", ",", "\"\<continue\>\"",
",", "\"\<default\>\"", ",", "\"\<do\>\"", ",", "\"\<double\>\"",
",", "\"\<else\>\"", ",", "\"\<enum\>\"", ",", "\"\<extern\>\"",
",", "\"\<float\>\"", ",", "\"\<for\>\"", ",", "\"\<goto\>\"",
",", "\"\<if\>\"", ",", "\"\<int\>\"", ",", "\"\<long\>\"", ",",
"\"\<register\>\"", ",", "\"\<return\>\"", ",", "\"\<short\>\"",
",", "\"\<signed\>\"", ",", "\"\<sizeof\>\"", ",",
"\"\<static\>\"", ",", "\"\<struct\>\"", ",", "\"\<switch\>\"",
",", "\"\<typedef\>\"", ",", "\"\<union\>\"", ",",
"\"\<unsigned\>\"", ",", "\"\<void\>\"", ",", "\"\<volatile\>\"",
",", "\"\<while\>\""}], "\[IndentingNewLine]", "}"}]}]}],
"}"}]}], ",", "\[IndentingNewLine]",
RowBox[{"\"\<Numbers\>\"", "\[Rule]",
RowBox[{"\"\<Color\>\"", "\[Rule]", "Pink"}]}], ",",
"\[IndentingNewLine]",
RowBox[{"\"\<Strings\>\"", "\[Rule]",
RowBox[{"\"\<Color\>\"", "\[Rule]", "Blue"}]}]}],
"\[IndentingNewLine]", "}"}]}], ",", "\[IndentingNewLine]",
RowBox[{"CachingOptions", "\[Rule]", " ",
RowBox[{"{", "\[IndentingNewLine]",
RowBox[{
RowBox[{"\"\<CacheTokenSets\>\"", "\[Rule]", "True"}], ",",
"\[IndentingNewLine]",
RowBox[{"\"\<CacheIndividualTokens\>\"", "\[Rule]", "True"}], ",",
"\[IndentingNewLine]",
RowBox[{"\"\<CacheTokenizer\>\"", "\[Rule]", " ", "True"}]}],
"\[IndentingNewLine]", "}"}]}], ",", "\[IndentingNewLine]",
RowBox[{"TokenizerOptions", "\[Rule]",
RowBox[{"\"\<AutomaticTokenizerOptions\>\"", "\[Rule]",
RowBox[{"\"\<LiteralPattern\>\"", "\[Rule]",
RowBox[{
RowBox[{"(",
RowBox[{"WordCharacter", "|", "\"\<_\>\""}], ")"}], ".."}]}]}]}],
",", "\[IndentingNewLine]",
RowBox[{"SymbolNames", "\[RuleDelayed]",
RowBox[{"{", "\[IndentingNewLine]",
RowBox[{
RowBox[{"\"\<CellGenerator\>\"", "\[RuleDelayed]",
RowBox[{"Symbol", "[", "\"\<GetCCellAlt\>\"", "]"}]}], ",",
"\[IndentingNewLine]",
RowBox[{
"\"\<EventActions\>\"", "\[RuleDelayed]", " ", "eventActionsAlt"}]}],
"\[IndentingNewLine]", "}"}]}]}], "\[IndentingNewLine]", "]"}],
";"}]], "Input",
CellChangeTimes->{{3.5347769193085938`*^9, 3.534777009754883*^9}, {
3.534777079873047*^9, 3.5347770887158203`*^9}, {3.5373740617216797`*^9,
3.5373740985791016`*^9}, {3.5373743258740234`*^9, 3.5373744195585938`*^9}, {
3.5373744758251953`*^9, 3.537374480305664*^9}}]
}, Open ]],
Cell[CellGroupData[{
Cell["Loading the generated package", "Subsubsection",
CellChangeTimes->{{3.5347784331328125`*^9, 3.5347784493378906`*^9}}],
Cell["We now load it", "Text",
CellChangeTimes->{{3.534777569057617*^9, 3.5347775719628906`*^9}}],
Cell[BoxData[
RowBox[{"Needs", "[", "\"\<CCodeHighlighterAlt`\>\"", "]"}]], "Input",
CellChangeTimes->{{3.534777139696289*^9, 3.534777140336914*^9}, {
3.537374126875*^9, 3.5373741271240234`*^9}}]
}, Open ]],
Cell[CellGroupData[{
Cell["Using the highlighter", "Subsubsection",
CellChangeTimes->{{3.534778455959961*^9, 3.534778460251953*^9}}],
Cell["\<\
and use it (again, move the cursor to start the highlighter).\
\>", "Text",
CellChangeTimes->{{3.534777574890625*^9, 3.5347775831367188`*^9}, {
3.534777652591797*^9, 3.5347776616972656`*^9}}],
Cell[BoxData[
RowBox[{"CellPrint", "[", "\[IndentingNewLine]",
RowBox[{"Cell", "[",
RowBox[{
RowBox[{"TextData", "[",
RowBox[{
"{", "\[IndentingNewLine]",
"\"\<int test_ordering(void){\n int testarr[MAX_ELEMS] = \
{5,1,3,7,12,4,8,9,3,10,9,7,4,2,11};\n int order[MAX_ELEMS], \
permuted[MAX_ELEMS], len = 15;\n \n \
if(find_ordering(order,testarr,len)!=0){\n printf(\\\"Error in the \
ordering function\\\\n\\\");\n return 1; \n }\n \
print_integers(order,len);\n permute(permuted,testarr,order,len);\n \
print_integers(permuted,len);\n return 0; \n}\n\n\\\"This is a string\\\
\"\n12345 - \\\"This is a number\\\"\n\n\>\"", "}"}], "]"}], ",",
"\"\<Program\>\"", ",",
RowBox[{"CellEventActions", "\[Rule]", "eventActionsAlt"}], ",",
"\[IndentingNewLine]",
RowBox[{"Evaluatable", "\[Rule]", "True"}], ",",
RowBox[{"CellEvaluationFunction", "\[Rule]", "someCEvaluator"}], ",",
RowBox[{"CellFrameLabels", "\[Rule]",
RowBox[{"{",
RowBox[{
RowBox[{"{",
RowBox[{"None", ",", "\"\<C code\>\""}], "}"}], ",",
RowBox[{"{",
RowBox[{"None", ",", "None"}], "}"}]}], "}"}]}]}], "]"}],
"\[IndentingNewLine]", "]"}]], "Input",
CellChangeTimes->{{3.5347771618251953`*^9, 3.5347771624345703`*^9}, {
3.5347776082177734`*^9, 3.5347776329697266`*^9}, {3.5373741636503906`*^9,
3.537374176854492*^9}}],
Cell[TextData[{
StyleBox["int",
FontWeight->Bold,
FontColor->RGBColor[1, 0, 0]],
" ",
"test_ordering",
StyleBox["(",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
StyleBox["void",
FontWeight->Bold,
FontColor->RGBColor[1, 0, 0]],
StyleBox[")",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
StyleBox["{",
FontWeight->Bold,
FontColor->RGBColor[0.4, 0, 0]],
"\n ",
StyleBox["int",
FontWeight->Bold,
FontColor->RGBColor[1, 0, 0]],
" ",
"testarr",
StyleBox["[",
FontWeight->Bold,
FontColor->RGBColor[0, 1, 0]],
"MAX_ELEMS",
StyleBox["]",
FontWeight->Bold,
FontColor->RGBColor[0, 1, 0]],
" = ",
StyleBox["{",
FontWeight->Bold,
FontColor->RGBColor[0.4, 0, 0]],
StyleBox["5",
FontWeight->Plain,
FontColor->RGBColor[1, 0.5, 0.5]],
",",
StyleBox["1",
FontWeight->Plain,
FontColor->RGBColor[1, 0.5, 0.5]],
",",
StyleBox["3",
FontWeight->Plain,
FontColor->RGBColor[1, 0.5, 0.5]],
",",
StyleBox["7",
FontWeight->Plain,
FontColor->RGBColor[1, 0.5, 0.5]],
",",
StyleBox["12",
FontWeight->Plain,
FontColor->RGBColor[1, 0.5, 0.5]],
",",
StyleBox["4",
FontWeight->Plain,
FontColor->RGBColor[1, 0.5, 0.5]],
",",
StyleBox["8",
FontWeight->Plain,
FontColor->RGBColor[1, 0.5, 0.5]],
",",
StyleBox["9",
FontWeight->Plain,
FontColor->RGBColor[1, 0.5, 0.5]],
",",
StyleBox["3",
FontWeight->Plain,
FontColor->RGBColor[1, 0.5, 0.5]],
",",
StyleBox["10",
FontWeight->Plain,
FontColor->RGBColor[1, 0.5, 0.5]],
",",
StyleBox["9",
FontWeight->Plain,
FontColor->RGBColor[1, 0.5, 0.5]],
",",
StyleBox["7",
FontWeight->Plain,
FontColor->RGBColor[1, 0.5, 0.5]],
",",
StyleBox["4",
FontWeight->Plain,
FontColor->RGBColor[1, 0.5, 0.5]],
",",
StyleBox["2",
FontWeight->Plain,
FontColor->RGBColor[1, 0.5, 0.5]],
",",
StyleBox["11",
FontWeight->Plain,
FontColor->RGBColor[1, 0.5, 0.5]],
StyleBox["}",
FontWeight->Bold,
FontColor->RGBColor[0.4, 0, 0]],
";\n ",
StyleBox["int",
FontWeight->Bold,
FontColor->RGBColor[1, 0, 0]],
" ",
"order",
StyleBox["[",
FontWeight->Bold,
FontColor->RGBColor[0, 1, 0]],
"MAX_ELEMS",
StyleBox["]",
FontWeight->Bold,
FontColor->RGBColor[0, 1, 0]],
", ",
"permuted",
StyleBox["[",
FontWeight->Bold,
FontColor->RGBColor[0, 1, 0]],
"MAX_ELEMS",
StyleBox["]",
FontWeight->Bold,
FontColor->RGBColor[0, 1, 0]],
", ",
"len",
" = ",
StyleBox["15",
FontWeight->Plain,
FontColor->RGBColor[1, 0.5, 0.5]],
";\n \n ",
StyleBox["if",
FontWeight->Bold,
FontColor->RGBColor[1, 0, 0]],
StyleBox["(",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
"find_ordering",
StyleBox["(",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
"order",
",",
"testarr",
",",
"len",
StyleBox[")",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
StyleBox["!=",
FontWeight->Bold,
FontColor->RGBColor[0, 1, 0]],
StyleBox["0",
FontWeight->Plain,
FontColor->RGBColor[1, 0.5, 0.5]],
StyleBox[")",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
StyleBox["{",
FontWeight->Bold,
FontColor->RGBColor[0.4, 0, 0]],
"\n ",
StyleBox["printf",
FontWeight->Bold,
FontColor->RGBColor[0.6, 0.4, 0.2]],
StyleBox["(",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
StyleBox["\"Error in the ordering function\\n\"",
FontWeight->Bold,
FontColor->RGBColor[0, 0, 1]],
StyleBox[")",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
";\n ",
StyleBox["return",
FontWeight->Bold,
FontColor->RGBColor[1, 0, 0]],
" ",
StyleBox["1",
FontWeight->Plain,
FontColor->RGBColor[1, 0.5, 0.5]],
"; \n ",
StyleBox["}",
FontWeight->Bold,
FontColor->RGBColor[0.4, 0, 0]],
"\n ",
"print_integers",
StyleBox["(",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
"order",
",",
"len",
StyleBox[")",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
";\n ",
"permute",
StyleBox["(",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
"permuted",
",",
"testarr",
",",
"order",
",",
"len",
StyleBox[")",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
";\n ",
"print_integers",
StyleBox["(",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
"permuted",
",",
"len",
StyleBox[")",
FontWeight->Bold,
FontColor->GrayLevel[0.5]],
";\n ",
StyleBox["return",
FontWeight->Bold,
FontColor->RGBColor[1, 0, 0]],
" ",
StyleBox["0",
FontWeight->Plain,
FontColor->RGBColor[1, 0.5, 0.5]],
"; \n",
StyleBox["}",
FontWeight->Bold,
FontColor->RGBColor[0.4, 0, 0]],
"\n\n",
StyleBox["\"This is a string\"",
FontWeight->Bold,
FontColor->RGBColor[0, 0, 1]],
"\n",
StyleBox["12345",
FontWeight->Plain,
FontColor->RGBColor[1, 0.5, 0.5]],
" ",
StyleBox["-",
FontWeight->Bold,
FontColor->RGBColor[0, 1, 0]],
" ",
StyleBox["\"This is a number\"",
FontWeight->Bold,
FontColor->RGBColor[0, 0, 1]],
"\n\n"
}], "Program",
ShowSelection->False,
Evaluatable->True,
CellEvaluationFunction->$CellContext`someCEvaluator,
GeneratedCell->True,
CellAutoOverwrite->True,
CellEventActions->{
"LeftArrowKeyDown" :> CCodeHighlighterAlt`Private`keyAction[
Function[{CCodeHighlighterAlt`Private`pos$},
CCodeHighlighterAlt`Private`cellHighlightRule[
CCodeHighlighterAlt`Private`HighlightFunction[
CCodeHighlighterAlt`Private`pos$]]], -1, $CellContext`eventActionsAlt],
"RightArrowKeyDown" :> CCodeHighlighterAlt`Private`keyAction[
Function[{CCodeHighlighterAlt`Private`pos$},
CCodeHighlighterAlt`Private`cellHighlightRule[
CCodeHighlighterAlt`Private`HighlightFunction[
CCodeHighlighterAlt`Private`pos$ + 1]]],
1, $CellContext`eventActionsAlt], "MouseOver" :>
CCodeHighlighterAlt`Private`mouseAction[], {"KeyDown", " "} :>
CCodeHighlighterAlt`Private`keyAction[
Function[{CCodeHighlighterAlt`Private`pos$},
CCodeHighlighterAlt`Private`cellHighlightRule[
CCodeHighlighterAlt`Private`CharacterEnterHighlightFunction[
" ", CCodeHighlighterAlt`Private`pos$ + 1]]],
1, $CellContext`eventActionsAlt]},
CellFrameLabels->{{None, "C code"}, {None, None}},
CellChangeTimes->{3.5373746785566406`*^9}],
Cell[TextData[{
"We could, as previously, also use the higher-level cell-generating \
functions, which in this case is ",
StyleBox["CCodeHighlighterAlt`GetCCellAlt",
FontWeight->"Bold",
FontSlant->"Italic"]
}], "Text",
CellChangeTimes->{{3.5347784692304688`*^9, 3.5347785314121094`*^9}, {
3.5373745073603516`*^9, 3.5373745145322266`*^9}}]
}, Open ]],
Cell[CellGroupData[{
Cell["Other customizations", "Subsubsection",
CellChangeTimes->{{3.534778047638672*^9, 3.534778051489258*^9}}],
Cell["\<\
There are a number of other customizations that are available.
We can, for example, enable highlighting to react also on letter key pressed. \
This will, however, slow it down. This customization is therefore switched \
off by default.
We can also supply our own tokenizer, if the one that is generated \
automatically does not behave quite satisfactory. Note that there is some \
flexibility also in the configuration of the default tokenizer. For example, \
here, C literals allow blanks in the middle, which may not be accounted for \
by a default tokenizer, but we enabled this with the setting\
\>", "Text",
CellChangeTimes->{{3.5347780570566406`*^9, 3.5347783083564453`*^9}, {
3.5373747614414062`*^9, 3.5373747841865234`*^9}}],
Cell[BoxData[
RowBox[{" ",
RowBox[{"TokenizerOptions", "\[Rule]",
RowBox[{"\"\<AutomaticTokenizerOptions\>\"", "\[Rule]",
RowBox[{"\"\<LiteralPattern\>\"", "\[Rule]",
RowBox[{
RowBox[{"(",
RowBox[{"WordCharacter", "|", "\"\<_\>\""}], ")"}],
".."}]}]}]}]}]], "Input",
CellChangeTimes->{{3.5347780570566406`*^9, 3.5347783171035156`*^9}, {
3.537374772114258*^9, 3.5373747723847656`*^9}}]
}, Open ]]
}, Open ]]
}, Open ]],
Cell[CellGroupData[{
Cell["Bugs and issues", "Section",
CellChangeTimes->{{3.5347839510976562`*^9, 3.5347839566220703`*^9}},
FontWeight->"Plain"],
Cell[CellGroupData[{
Cell["\<\
Unwanted auto-scroll for large code cells\
\>", "Subsection",
CellChangeTimes->{{3.534783963495117*^9, 3.5347839744941406`*^9}},
FontWeight->"Plain"],
Cell["\<\
This can be seen on the C example above. The strange thing is that I seem to \
have earlier versions of this code where event-handling and rendering code \
looks exactly the same, but this effect is absent (it used to be there until \
I inserted the AutoScroll -> False into all relevant places)\
\>", "Text",
CellChangeTimes->{{3.5347839772939453`*^9, 3.5347840601552734`*^9}}]
}, Closed]],
Cell["\<\
User- defined tokenizer - unfinished\
\>", "Subsection",
CellChangeTimes->{{3.53478406528125*^9, 3.5347840863095703`*^9},
3.5347841949882812`*^9},
FontWeight->"Plain"],
Cell["\<\
Don\[CloseCurlyQuote]t correctly handle string escape characters\
\>", "Subsection",
CellChangeTimes->{{3.534784095026367*^9, 3.5347841143710938`*^9}},
FontWeight->"Plain"],
Cell["\<\
Don\[CloseCurlyQuote]t have much customizibility on the level of already \
generated package\
\>", "Subsection",
CellChangeTimes->{{3.5347841355185547`*^9, 3.5347841544970703`*^9}},
FontWeight->"Plain"],
Cell["\<\
Don\[CloseCurlyQuote]t have proper option checks for the main package (the \
code generator)\
\>", "Subsection",
CellChangeTimes->{{3.534784164803711*^9, 3.534784181915039*^9}},
FontWeight->"Plain"],
Cell["\<\
A possible further optimization would be to make it possible to disable \
bracket- and paren - matching\
\>", "Subsection",
CellChangeTimes->{{3.534784209623047*^9, 3.534784239635742*^9}},
FontWeight->"Plain"],
Cell["\<\
Generated package code is not pretty-printed and therefore not very easy to \
read\
\>", "Subsection",
CellChangeTimes->{{3.5347842566816406`*^9, 3.53478427771875*^9}},
FontWeight->"Plain"]
}, Open ]]
}, Open ]]
},
WindowSize->{1897, 910},
WindowMargins->{{0, Automatic}, {Automatic, 0}},
ShowSelection->True,
Magnification->1.8000001907348633`,
FrontEndVersion->"8.0 for Microsoft Windows (64-bit) (November 7, 2010)",
StyleDefinitions->"Default.nb"
]
(* End of Notebook Content *)
(* Internal cache information *)
(*CellTagsOutline
CellTagsIndex->{
"Info3537385458-7027350"->{
Cell[32940, 1060, 143, 2, 72, "Print",
CellTags->"Info3537385458-7027350"],
Cell[33086, 1064, 6381, 116, 969, "Print",
CellTags->"Info3537385458-7027350"]}
}
*)
(*CellTagsIndex
CellTagsIndex->{
{"Info3537385458-7027350", 63342, 1877}
}
*)
(*NotebookFileOutline
Notebook[{
Cell[CellGroupData[{
Cell[579, 22, 136, 3, 88, "Subtitle"],
Cell[CellGroupData[{
Cell[740, 29, 151, 4, 125, "Section"],
Cell[894, 35, 94, 1, 52, "Input"],
Cell[991, 38, 186, 3, 52, "Input"],
Cell[CellGroupData[{
Cell[1202, 45, 158, 4, 64, "Subsection"],
Cell[1363, 51, 282, 6, 50, "Text"],
Cell[1648, 59, 348, 6, 81, "Text"],
Cell[1999, 67, 5286, 89, 693, "Input"],
Cell[7288, 158, 225, 4, 50, "Text"],
Cell[CellGroupData[{
Cell[7538, 166, 122, 2, 46, "Subsubsection"],
Cell[7663, 170, 1671, 36, 203, "Text"]
}, Open ]],
Cell[CellGroupData[{
Cell[9371, 211, 136, 1, 46, "Subsubsection"],
Cell[9510, 214, 124, 1, 50, "Text"],
Cell[CellGroupData[{
Cell[9659, 219, 156, 2, 52, "Input"],
Cell[9818, 223, 374, 5, 51, "Output"]
}, Open ]],
Cell[10207, 231, 128, 1, 50, "Text"],
Cell[10338, 234, 319, 7, 52, "Input"]
}, Open ]],
Cell[CellGroupData[{
Cell[10694, 246, 112, 1, 46, "Subsubsection"],
Cell[10809, 249, 121, 1, 50, "Text"],
Cell[10933, 252, 148, 2, 52, "Input"]
}, Open ]],
Cell[CellGroupData[{
Cell[11118, 259, 255, 7, 46, "Subsubsection"],
Cell[11376, 268, 277, 8, 50, "Text"],
Cell[CellGroupData[{
Cell[11678, 280, 158, 2, 52, "Input"],
Cell[11839, 284, 2079, 43, 262, "Output"]
}, Open ]],
Cell[13933, 330, 311, 8, 50, "Text"],
Cell[14247, 340, 481, 11, 81, "Text"],
Cell[14731, 353, 1465, 30, 565, "Input"],
Cell[16199, 385, 6241, 280, 391, "Program",
Evaluatable->True]
}, Open ]],
Cell[CellGroupData[{
Cell[22477, 670, 245, 7, 46, "Subsubsection"],
Cell[22725, 679, 416, 9, 81, "Text"],
Cell[23144, 690, 171, 3, 50, "Text"],
Cell[23318, 695, 1238, 26, 565, "Input"],
Cell[24559, 723, 6694, 288, 391, "Program",
Evaluatable->True]
}, Open ]],
Cell[CellGroupData[{
Cell[31290, 1016, 117, 1, 46, "Subsubsection"],
Cell[31410, 1019, 396, 6, 81, "Text"],
Cell[CellGroupData[{
Cell[31831, 1029, 187, 3, 52, "Input"],
Cell[32021, 1034, 560, 11, 51, "Output"]
}, Open ]],
Cell[32596, 1048, 98, 1, 50, "Text"],
Cell[CellGroupData[{
Cell[32719, 1053, 196, 3, 52, "Input"],
Cell[CellGroupData[{
Cell[32940, 1060, 143, 2, 72, "Print",
CellTags->"Info3537385458-7027350"],
Cell[33086, 1064, 6381, 116, 969, "Print",
CellTags->"Info3537385458-7027350"]
}, Open ]]
}, Open ]],
Cell[39494, 1184, 108, 1, 50, "Text"],
Cell[CellGroupData[{
Cell[39627, 1189, 681, 12, 437, "Input"],
Cell[40311, 1203, 1451, 30, 409, "Output"]
}, Open ]],
Cell[41777, 1236, 123, 1, 50, "Text"]
}, Open ]]
}, Open ]],
Cell[CellGroupData[{
Cell[41949, 1243, 146, 2, 64, "Subsection"],
Cell[CellGroupData[{
Cell[42120, 1249, 129, 1, 46, "Subsubsection"],
Cell[42252, 1252, 178, 4, 50, "Text"],
Cell[42433, 1258, 195, 4, 52, "Input"]
}, Open ]],
Cell[CellGroupData[{
Cell[42665, 1267, 177, 2, 46, "Subsubsection"],
Cell[42845, 1271, 363, 6, 81, "Text"],
Cell[43211, 1279, 229, 6, 142, "Text"],
Cell[43443, 1287, 128, 1, 50, "Text"],
Cell[43574, 1290, 7281, 127, 1279, "Input"]
}, Open ]],
Cell[CellGroupData[{
Cell[50892, 1422, 124, 1, 46, "Subsubsection"],
Cell[51019, 1425, 98, 1, 50, "Text"],
Cell[51120, 1428, 199, 3, 52, "Input"]
}, Open ]],
Cell[CellGroupData[{
Cell[51356, 1436, 112, 1, 46, "Subsubsection"],
Cell[51471, 1439, 204, 4, 50, "Text"],
Cell[51678, 1445, 1439, 30, 725, "Input"],
Cell[53120, 1477, 6143, 273, 522, "Program",
Evaluatable->True],
Cell[59266, 1752, 347, 8, 50, "Text"]
}, Open ]],
Cell[CellGroupData[{
Cell[59650, 1765, 111, 1, 46, "Subsubsection"],
Cell[59764, 1768, 748, 14, 203, "Text"],
Cell[60515, 1784, 427, 10, 57, "Input"]
}, Open ]]
}, Open ]]
}, Open ]],
Cell[CellGroupData[{
Cell[61003, 1801, 126, 2, 125, "Section"],
Cell[CellGroupData[{
Cell[61154, 1807, 161, 4, 64, "Subsection"],
Cell[61318, 1813, 389, 6, 4921, "Text"]
}, Closed]],
Cell[61722, 1822, 183, 5, 46, "Subsection"],
Cell[61908, 1829, 184, 4, 46, "Subsection"],
Cell[62095, 1835, 214, 5, 46, "Subsection"],
Cell[62312, 1842, 210, 5, 46, "Subsection"],
Cell[62525, 1849, 221, 5, 46, "Subsection"],
Cell[62749, 1856, 201, 5, 46, "Subsection"]
}, Open ]]
}, Open ]]
}
]
*)
(* End of internal cache information *)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment