Skip to content

Commit

Permalink
Merge pull request #454 from WolframResearch/feature/inline-wl-code-e…
Browse files Browse the repository at this point in the history
…xpansion

Inline WL code input boxes
  • Loading branch information
rhennigan authored Nov 14, 2023
2 parents 1b5e117 + 16b2937 commit d0a8eca
Show file tree
Hide file tree
Showing 6 changed files with 277 additions and 5 deletions.
Binary file modified Assets/DisplayFunctions.wxf
Binary file not shown.
28 changes: 28 additions & 0 deletions Developer/Resources/Styles.wl
Original file line number Diff line number Diff line change
Expand Up @@ -170,6 +170,12 @@ Cell[
Symbol[ "Wolfram`Chatbook`ChatbookAction" ][ "InsertInlineReference", "ModifierTemplate", $CellContext`cell ]
]
,
(* Insert WL code input template: *)
{ "KeyDown", "\\" } :> With[ { $CellContext`cell = EvaluationCell[ ] },
Quiet @ Needs[ "Wolfram`Chatbook`" -> None ];
Symbol[ "Wolfram`Chatbook`ChatbookAction" ][ "InsertInlineReference", "WLTemplate", $CellContext`cell ]
]
,
(* Highlight cells that will be included in chat context: *)
"MouseEntered" :> With[ { $CellContext`cell = EvaluationCell[ ] },
Quiet @ Needs[ "Wolfram`Chatbook`" -> None ];
Expand Down Expand Up @@ -1059,6 +1065,28 @@ Cell[
]


(* ::Subsection::Closed:: *)
(*ChatbookWLTemplate*)


Cell[
StyleData["ChatbookWLTemplate"],
TemplateBoxOptions -> {
DisplayFunction -> (
NamespaceBox["ChatbookWLTemplateID",
DynamicModuleBox[{},
DynamicBox[ToBoxes @ Wolfram`Chatbook`InlineReferences`wlTemplateBoxes[1, #input, #state, #uuid]],
Initialization :> (
Quiet @ Needs[ "Wolfram`Chatbook`" -> None ];
Wolfram`Chatbook`InlineReferences`Private`$lastInlineReferenceCell = EvaluationCell[ ]
)
]
]&),
InterpretationFunction -> (InterpretationBox["", RowBox[{"\\",#input}]]&)
}
]


(* ::Section::Closed:: *)
(*Misc Styles*)

Expand Down
41 changes: 40 additions & 1 deletion FrontEnd/StyleSheets/Chatbook.nb
Original file line number Diff line number Diff line change
Expand Up @@ -1161,7 +1161,7 @@ Notebook[
],
Cell[
StyleData["ChatStyleSheetInformation"],
TaggingRules -> <|"StyleSheetVersion" -> "1.3.1.3908279596"|>
TaggingRules -> <|"StyleSheetVersion" -> "1.3.1.3908948274"|>
],
Cell[
StyleData["Text"],
Expand Down Expand Up @@ -1621,6 +1621,15 @@ Notebook[
cell
]
],
{"KeyDown", "\\"} :>
With[ { cell = EvaluationCell[] },
Quiet[Needs["Wolfram`Chatbook`" -> None]];
Symbol["Wolfram`Chatbook`ChatbookAction"][
"InsertInlineReference",
"WLTemplate",
cell
]
],
"MouseEntered" :>
With[ { cell = EvaluationCell[] },
Quiet[Needs["Wolfram`Chatbook`" -> None]];
Expand Down Expand Up @@ -17058,6 +17067,36 @@ Notebook[
(InterpretationBox["", StringJoin["!", #input]] &)
}
],
Cell[
StyleData["ChatbookWLTemplate"],
TemplateBoxOptions -> {
DisplayFunction ->
(Function[
NamespaceBox[
"ChatbookWLTemplateID",
DynamicModuleBox[
{ },
DynamicBox[
ToBoxes[
Wolfram`Chatbook`InlineReferences`wlTemplateBoxes[
1,
#input,
#state,
#uuid
]
]
],
Initialization :>
(Quiet[Needs["Wolfram`Chatbook`" -> None]];
Wolfram`Chatbook`InlineReferences`Private`$lastInlineReferenceCell =
EvaluationCell[])
]
]
]),
InterpretationFunction ->
(InterpretationBox["", RowBox[{"\\", #input}]] &)
}
],
Cell[
StyleData[
"InlineReferenceText",
Expand Down
6 changes: 5 additions & 1 deletion Source/Chatbook/Actions.wl
Original file line number Diff line number Diff line change
Expand Up @@ -269,6 +269,7 @@ InsertInlineReference // endDefinition;
(*insertInlineReference*)
insertInlineReference // beginDefinition;

(* FIXME: these four are unused, need to remove relevant definitions *)
insertInlineReference[ "Persona" , args___ ] := insertPersonaInputBox @ args;
insertInlineReference[ "TrailingFunction", args___ ] := insertTrailingFunctionInputBox @ args;
insertInlineReference[ "Function" , args___ ] := insertFunctionInputBox @ args;
Expand All @@ -277,6 +278,7 @@ insertInlineReference[ "Modifier" , args___ ] := insertModifierInputBox @
insertInlineReference[ "PersonaTemplate" , args___ ] := insertPersonaTemplate @ args;
insertInlineReference[ "FunctionTemplate", args___ ] := insertFunctionTemplate @ args;
insertInlineReference[ "ModifierTemplate", args___ ] := insertModifierTemplate @ args;
insertInlineReference[ "WLTemplate" , args___ ] := insertWLTemplate @ args;

insertInlineReference // endDefinition;

Expand Down Expand Up @@ -635,7 +637,7 @@ constructChatObject // beginDefinition;

(* cSpell: ignore bdprompt *)
constructChatObject[ messages_List ] :=
With[ { chat = Quiet[ ChatObject @ standardizeMessageKeys @ messages, ChatObject::bdprompt ] },
With[ { chat = Quiet[ chatObject @ standardizeMessageKeys @ messages, ChatObject::bdprompt ] },
chat /; MatchQ[ chat, _chatObject ]
];

Expand All @@ -644,6 +646,8 @@ constructChatObject[ messages_List ] :=

constructChatObject // endDefinition;

chatObject := chatObject = Symbol[ "System`ChatObject" ];

(* ::**************************************************************************************************************:: *)
(* ::Subsubsection::Closed:: *)
(*standardizeMessageKeys*)
Expand Down
189 changes: 189 additions & 0 deletions Source/Chatbook/InlineReferences.wl
Original file line number Diff line number Diff line change
Expand Up @@ -14,10 +14,12 @@ BeginPackage[ "Wolfram`Chatbook`InlineReferences`" ];
`insertPersonaTemplate;
`insertFunctionTemplate;
`insertModifierTemplate;
`insertWLTemplate;

`personaTemplateBoxes;
`functionTemplateBoxes;
`modifierTemplateBoxes;
`wlTemplateBoxes;

`parseInlineReferences;
`resolveLastInlineReference;
Expand Down Expand Up @@ -1934,6 +1936,193 @@ insertFunctionTemplate[ name_String, parent_CellObject, nbo_NotebookObject ] :=
];


(* ::Section::Closed:: *)
(*WL Template*)


(* ::Subsection::Closed:: *)
(*setWLState*)


SetAttributes[setWLState, HoldFirst]

setWLState[state_, "Input", input_] := (
state = "Input";
MathLink`CallFrontEnd[FrontEnd`BoxReferenceFind[
FE`BoxReference[MathLink`CallFrontEnd[FrontEnd`Value[FEPrivate`Self[]]],
{FE`Parent["ChatbookWLTemplateID"]}],
AutoScroll -> True
]];
FrontEndExecute[FrontEnd`FrontEndToken["MoveNextPlaceHolder"]];
)

setWLState[state_, "Chosen", input_] :=
Enclose[
With[{cellobj = EvaluationCell[]},
state = "Chosen";
SelectionMove[cellobj, All, Cell];
FrontEndExecute[FrontEnd`FrontEndToken["MoveNext"]];
CurrentValue[cellobj, TaggingRules] = <| "WLCode" -> input |>;
]
,
throwInternalFailure[ setWLState[state, "Chosen", input], ## ]&
]

setWLState[ state_, "Replace", input_ ] := (
SelectionMove[ EvaluationCell[ ], All, Cell ];
NotebookWrite[
InputNotebook[ ],
First[
FrontEndExecute @ FrontEnd`ExportPacket[ Cell @ BoxData @ RowBox @ { "\\", input }, "PlainText" ],
"\\"
]
]
);


(* ::Subsection::Closed:: *)
(*wlTemplateBoxes*)


SetAttributes[wlTemplateBoxes, HoldRest];

wlTemplateBoxes[version: 1, input_, state_, uuid_, opts: OptionsPattern[]] /; state === "Input" :=
EventHandler[
Style[
Framed[
Grid[
{
{
RawBoxes[TemplateBox[{}, "AssistantEvaluate"]],
InputField[
Dynamic[ input ],
Boxes,
Alignment -> { Left, Baseline },
ContinuousAction -> False,
BaselinePosition -> Baseline,
FieldSize -> { { 5, Infinity }, Automatic },
Appearance -> "Frameless",
(*ContentPadding -> False,*)
FrameMargins -> 0,
BoxID -> uuid,
BaseStyle -> {
"Notebook",
"Input",
ShowCodeAssist -> True,
ShowSyntaxStyles -> True,
FontFamily -> "Source Sans Pro",
FontSize -> 14
}
] // overrideKeyEvents
}
},
Spacings -> 0,
Alignment -> { Automatic, Baseline },
BaselinePosition -> { 1, 2 }
],
BaselinePosition -> Baseline,
FrameStyle -> GrayLevel[0.9],
ImageMargins -> {{1,1},{0,0}},
$frameOptions
],
"Text",
ShowStringCharacters -> False
],
{
(*{ "KeyDown", "!" } :> NotebookWrite[ EvaluationNotebook[ ], "!" ],*)
"EscapeKeyDown" :> setWLState[state, "Replace", input],
"ReturnKeyDown" :> setWLState[state, "Chosen", input]
}
]

wlTemplateBoxes[ version: 1, input_, state_, uuid_, opts: OptionsPattern[ ] ] /; state === "Chosen" :=
Button[
NotebookTools`Mousedown @@ MapThread[
Framed[
Grid[
{
{
RawBoxes @ TemplateBox[ { }, "AssistantEvaluate" ],
Style[
RawBoxes @ input,
"Input",
ShowCodeAssist -> True,
ShowSyntaxStyles -> True,
FontFamily -> "Source Sans Pro",
FontSize -> 14,
ShowStringCharacters -> True
]
}
},
Spacings -> 0,
Alignment -> { Automatic, Baseline }
],
BaselinePosition -> { 1, 2 },
RoundingRadius -> 2,
Background -> #1,
FrameStyle -> #2,
FrameMargins -> 2,
ImageMargins -> { { 1, 1 }, { 0, 0 } }
] &,
{
{ GrayLevel[ 0.95 ], GrayLevel[ 0.975 ], GrayLevel[ 1.0 ] },
{ GrayLevel[ 0.90 ], GrayLevel[ 0.800 ], GrayLevel[ 0.9 ] }
}
],
setWLState[ state, "Input", input ]
,
Appearance -> "Suppressed",
BaseStyle -> { },
DefaultBaseStyle -> { },
BaselinePosition -> Baseline
];

(* FIXME: Add a wlTemplateBoxes rule for unknown version number *)


(* ::Subsection::Closed:: *)
(*wlTemplateCell*)


wlTemplateCell[input_String, state: ("Input" | "Chosen"), uuid_String] :=
Cell[BoxData[FormBox[
TemplateBox[<|"input" -> input, "state" -> state, "uuid" -> uuid|>,
"ChatbookWLTemplate"
], TextForm]],
"InlineWLReference",
Background -> None,
Deployed -> True
]


(* ::Subsection::Closed:: *)
(*insertWLTemplate*)


insertWLTemplate[ cell_CellObject ] :=
insertWLTemplate[ cell, parentNotebook @ cell ];

insertWLTemplate[ parent_CellObject, nbo_NotebookObject ] :=
Module[ { uuid, cellexpr },
resolveInlineReferences @ parent;
uuid = CreateUUID[ ];
cellexpr = wlTemplateCell[ "", "Input", uuid ];
NotebookWrite[ nbo, cellexpr ];
(* FIXME: Can we get rid of the need for this UUID, and use BoxReference-something? *)
FrontEnd`MoveCursorToInputField[ nbo, uuid ]
];

insertWLTemplate[ name_String, cell_CellObject ] := insertWLTemplate[ name, cell, parentNotebook @ cell ];

insertWLTemplate[ name_String, parent_CellObject, nbo_NotebookObject ] :=
Module[ { uuid, cellexpr },
resolveInlineReferences @ ParentCell @ parent;
uuid = CreateUUID[ ];
cellexpr = wlTemplateCell[ name, "Input", uuid ];
NotebookWrite[ parent, cellexpr ];
FrontEnd`MoveCursorToInputField[ nbo, uuid ]
];

(* ::**************************************************************************************************************:: *)
(* ::Section::Closed:: *)
(*Cloud Docked Cell*)
Expand Down
18 changes: 15 additions & 3 deletions Source/Chatbook/Serialization.wl
Original file line number Diff line number Diff line change
Expand Up @@ -750,6 +750,17 @@ fasterCellToString0[ TemplateBox[ KeyValuePattern[ "input" -> string_ ], "TeXAss
"$" <> string <> "$"
);

(* Inline WL code template *)
fasterCellToString0[ TemplateBox[ KeyValuePattern[ "input" -> input_ ], "ChatbookWLTemplate", ___ ] ] :=
Replace[
Quiet[ ToExpression[ input, StandardForm ], ToExpression::esntx ],
{
string_String? StringQ :> string,
$Failed :> "\n\n[Inline parse failure: " <> ToString[ fasterCellToString0 @ input, InputForm ] <> "]",
expr_ :> fasterCellToString0 @ ToBoxes @ expr
}
];

(* Other *)
fasterCellToString0[ TemplateBox[ args_, name_String, ___ ] ] :=
With[ { f = $templateBoxRules @ name },
Expand Down Expand Up @@ -966,10 +977,11 @@ fasterCellToString0[ cell: Cell[ a_, ___ ] ] :=
fasterCellToString0 @ a
];

fasterCellToString0[ InterpretationBox[ _, expr_, ___ ] ] := (
fasterCellToString0[ InterpretationBox[ _, expr_, ___ ] ] :=
With[ { held = replaceCellContext @ HoldComplete @ expr },
needsBasePrompt[ "WolframLanguage" ];
inputFormString @ Unevaluated @ expr
);
Replace[ held, HoldComplete[ e_ ] :> inputFormString @ Unevaluated @ e ]
];

fasterCellToString0[ Cell[ TextData @ { _, _, text_String, _, Cell[ _, "ExampleCount", ___ ] }, ___ ] ] :=
fasterCellToString0 @ text;
Expand Down

0 comments on commit d0a8eca

Please sign in to comment.