Skip to content

Commit

Permalink
Merge pull request #626 from WolframResearch/bugfix/misc-fixes
Browse files Browse the repository at this point in the history
Minor improvements and fixes
  • Loading branch information
rhennigan authored Mar 16, 2024
2 parents e18432a + dd8be3f commit 6e5b444
Show file tree
Hide file tree
Showing 3 changed files with 98 additions and 10 deletions.
100 changes: 92 additions & 8 deletions Source/Chatbook/Formatting.wl
Original file line number Diff line number Diff line change
Expand Up @@ -76,8 +76,8 @@ $externalLanguageRules = Replace[
{ 1 }
];

$$mdRow1 = WhitespaceCharacter... ~~ "|" ~~ Except[ "\n" ].. ~~ "|" ~~ WhitespaceCharacter... ~~ ("\n"|EndOfString);
$$mdRow2 = Except[ "\n" ].. ~~ Repeated[ ("|" ~~ Except[ "\n" ]..), { 2, Infinity } ] ~~ ("\n"|EndOfString);
$$mdRow1 = WhitespaceCharacter... ~~ "|" ~~ Except[ "\n" ]... ~~ "|" ~~ WhitespaceCharacter... ~~ ("\n"|EndOfString);
$$mdRow2 = Except[ "\n" ].. ~~ Repeated[ ("|" ~~ Except[ "\n" ]...), { 2, Infinity } ] ~~ ("\n"|EndOfString);
$$mdRow = $$mdRow1 | $$mdRow2;
$$mdTable = $$mdRow ~~ $$mdRow ..;

Expand All @@ -101,6 +101,7 @@ $autoOperatorRenderings = <|
|>;

$expressionURIPlaceholder = "\[LeftSkeleton]\[Ellipsis]\[RightSkeleton]";
$freeformPromptBox = StyleBox[ "\[FreeformPrompt]", FontColor -> RGBColor[ "#ff6f00" ], FontSize -> 9 ];

(* ::**************************************************************************************************************:: *)
(* ::Section::Closed:: *)
Expand All @@ -118,8 +119,13 @@ StringToBoxes // endExportedDefinition;
(* ::Subsection::Closed:: *)
(*FormatChatOutput*)
FormatChatOutput // beginDefinition;
FormatChatOutput[ output_ ] := FormatChatOutput[ output, <| "Status" -> "Finished" |> ];
FormatChatOutput[ output_, as_Association ] := formatChatOutput[ output, Lookup[ as, "Status", "Finished" ] ];

FormatChatOutput[ output_ ] :=
FormatChatOutput[ output, <| "Status" -> If[ TrueQ @ $dynamicText, "Streaming", "Finished" ] |> ];

FormatChatOutput[ output_, as_Association ] :=
formatChatOutput[ output, Lookup[ as, "Status", "Finished" ] ];

FormatChatOutput // endDefinition;
(* TODO: actual error handling for invalid arguments *)

Expand Down Expand Up @@ -219,7 +225,10 @@ makeResultCell0[ codeBlockCell[ language_String, code_String ] ] :=
StringTrim @ code
];

makeResultCell0[ inlineCodeCell[ code_String ] ] := makeInlineCodeCell @ code;
makeResultCell0[ inlineCodeCell[ code_String ] ] := ReplaceAll[
makeInlineCodeCell @ code,
"\[FreeformPrompt]" :> RuleCondition @ $freeformPromptBox
];

makeResultCell0[ mathCell[ math_String ] ] /; StringMatchQ[ math, (DigitCharacter|"."|","|" ").. ] :=
math;
Expand Down Expand Up @@ -933,7 +942,13 @@ $stringFormatRules = {
styleBox[ text, FontSlant -> Italic ],

"\\textbf{" ~~ text__ ~~ "}" /; StringFreeQ[ text, "{"|"}" ] :>
styleBox[ text, FontWeight -> Bold ]
styleBox[ text, FontWeight -> Bold ],

"\[FreeformPrompt]" :>
Cell @ BoxData @ TemplateBox[
{ $freeformPromptBox, "paclet:guide/KnowledgeRepresentationAndAccess#203374175" },
"HyperlinkPaclet"
]
};

(* ::**************************************************************************************************************:: *)
Expand Down Expand Up @@ -1429,7 +1444,7 @@ makeInteractiveCodeCell // beginDefinition;
(* TODO: define template boxes for these *)
makeInteractiveCodeCell[ language_, code_String ] /; $dynamicText :=
If[ TrueQ @ wolframLanguageQ @ language,
codeBlockFrame[ Cell[ BoxData @ code, "ChatCodeActive" ], code, language ],
codeBlockFrame[ Cell[ BoxData @ wlStringToBoxes @ code, "ChatCodeActive" ], code, language ],
codeBlockFrame[ Cell[ code, "ChatPreformatted" ], code, language ]
];

Expand Down Expand Up @@ -1481,9 +1496,78 @@ makeInteractiveCodeCell // endDefinition;
(* ::Subsubsection::Closed:: *)
(*wlStringToBoxes*)
wlStringToBoxes // beginDefinition;
wlStringToBoxes[ string_String ] := inlineExpressionURIs @ stringToBoxes @ preprocessSandboxString @ string;

wlStringToBoxes[ string_String ] /; $dynamicText := formatNLInputs @ string;

wlStringToBoxes[ string_String ] :=
formatNLInputs @ inlineExpressionURIs @ stringToBoxes @ preprocessSandboxString @ string;

wlStringToBoxes // endDefinition;

(* ::**************************************************************************************************************:: *)
(* ::Subsubsection::Closed:: *)
(*formatNLInputs*)
formatNLInputs // beginDefinition;

formatNLInputs[ string_String ] :=
StringReplace[
string,
"\[FreeformPrompt][\"" ~~ q: Except[ "\"" ].. ~~ ("\"]"|EndOfString) :>
ToString[ RawBoxes @ formatNLInputFast @ q, StandardForm ]
];

formatNLInputs[ boxes_ ] :=
boxes /. {
RowBox @ { "\[FreeformPrompt]", "[", q_String, "]" } /; StringMatchQ[ q, "\""~~Except[ "\""]..~~"\"" ] :>
RuleCondition @ If[ TrueQ @ $dynamicText, formatNLInputFast @ q, formatNLInputSlow @ q ]
,
RowBox @ { "\[FreeformPrompt]", "[", q_String } /; StringMatchQ[ q, "\""~~Except[ "\""]..~~("\""|"") ] :>
RuleCondition @ formatNLInputFast @ q
};

formatNLInputs // endDefinition;

(* ::**************************************************************************************************************:: *)
(* ::Subsubsection::Closed:: *)
(*formatNLInputFast*)
formatNLInputFast // beginDefinition;

formatNLInputFast[ q_String ] := OverlayBox[
{
FrameBox[
StyleBox[ q, ShowStringCharacters -> False, FontWeight -> Plain ],
BaseStyle -> { "CalculateInput", LineBreakWithin -> False },
FrameStyle -> GrayLevel[ 0.85 ],
RoundingRadius -> 3,
ImageMargins -> { { 5, 0 }, { 0, 0 } },
FrameMargins -> { { 6, 3 }, { 3, 3 } },
StripOnInput -> False
],
Append[ $freeformPromptBox, Background -> White ]
},
Alignment -> { Left, Baseline }
];

formatNLInputFast // endDefinition;

(* ::**************************************************************************************************************:: *)
(* ::Subsubsection::Closed:: *)
(*formatNLInputSlow*)
formatNLInputSlow // beginDefinition;

formatNLInputSlow[ query_String ] :=
With[ { h = ToExpression[ query, InputForm, HoldComplete ] },
(
formatNLInputSlow[ query ] =
ReplaceAll[
ToBoxes @ WolframAlpha[ ReleaseHold @ h, "LinguisticAssistant" ],
as: KeyValuePattern[ "open" -> { 1, 2 } ] :> RuleCondition @ <| as, "open" -> { 1 } |>
]
) /; MatchQ[ h, HoldComplete[ _String ] ]
];

formatNLInputSlow // endDefinition;

(* ::**************************************************************************************************************:: *)
(* ::Subsubsection::Closed:: *)
(*wolframLanguageQ*)
Expand Down
2 changes: 2 additions & 0 deletions Source/Chatbook/Sandbox.wl
Original file line number Diff line number Diff line change
Expand Up @@ -313,6 +313,7 @@ $defaultReadPaths := $defaultReadPaths = Select[
FileNameJoin @ { $UserBaseDirectory, "ApplicationData", "Parallel", "Preferences" },
FileNameJoin @ { $UserBaseDirectory, "ApplicationData", "Credentials" },
FileNameJoin @ { $UserBaseDirectory, "ApplicationData", "Astro" },
FileNameJoin @ { $UserBaseDirectory, "Knowledgebase" },
SystemInformation[ "FrontEnd", "DocumentationInformation" ][ "Directory" ],
ExpandFileName @ URL @ $LocalBase
},
Expand All @@ -337,6 +338,7 @@ $defaultWritePaths := $defaultWritePaths = Select[
FileNameJoin @ { $UserBaseDirectory, "ApplicationData", "Parallel", "Preferences" },
FileNameJoin @ { $UserBaseDirectory, "ApplicationData", "Credentials" },
FileNameJoin @ { $UserBaseDirectory, "ApplicationData", "Astro" },
FileNameJoin @ { $UserBaseDirectory, "Knowledgebase" },
FileNameJoin @ { ExpandFileName @ URL @ $LocalBase, "Resources" }
},
StringQ
Expand Down
6 changes: 4 additions & 2 deletions Source/Chatbook/Tools/Common.wl
Original file line number Diff line number Diff line change
Expand Up @@ -830,8 +830,10 @@ tool call.
The system will execute the requested tool call and you will receive a system message containing the result. \
You can then use this result to finish writing your response for the user.
You must write the TOOLCALL in your CURRENT response. \
Do not state that you will use a tool and end your message before making the tool call.
These are text-based tools, which you call by writing text, \
so you must write the tool call DURING your CURRENT response. \
Do not state that you will use a tool and end your message text before making the tool call \
or the entire system will fail catastrophically.
If a user asks you to use a specific tool, you MUST attempt to use that tool as requested, \
even if you think it will not work. \
Expand Down

0 comments on commit 6e5b444

Please sign in to comment.