Skip to content

Commit

Permalink
Merge pull request #428 from WolframResearch/main
Browse files Browse the repository at this point in the history
Release v1.2.4
  • Loading branch information
rhennigan authored Oct 24, 2023
2 parents a3b08a0 + 0d92df8 commit 78a8d8e
Show file tree
Hide file tree
Showing 9 changed files with 157 additions and 75 deletions.
Binary file modified Assets/DisplayFunctions.wxf
Binary file not shown.
6 changes: 3 additions & 3 deletions Developer/StylesheetBuilder.wl
Original file line number Diff line number Diff line change
Expand Up @@ -292,9 +292,9 @@ menuItem[ icon_, label_, action_String ] :=
Hold @ With[
{ $CellContext`cell = EvaluationCell[ ] },
{ $CellContext`root = ParentCell @ $CellContext`cell },
NotebookDelete @ $CellContext`cell;
Quiet @ Needs[ "Wolfram`Chatbook`" -> None ];
Symbol[ "Wolfram`Chatbook`ChatbookAction" ][ action, $CellContext`root ]
Symbol[ "Wolfram`Chatbook`ChatbookAction" ][ action, $CellContext`root ];
NotebookDelete @ $CellContext`cell;
]
];

Expand All @@ -303,8 +303,8 @@ menuItem[ icon_, label_, None ] :=
icon,
label,
Hold[
MessageDialog[ "Not Implemented" ];
NotebookDelete @ EvaluationCell[ ];
MessageDialog[ "Not Implemented" ]
]
];

Expand Down
34 changes: 23 additions & 11 deletions FrontEnd/StyleSheets/Chatbook.nb
Original file line number Diff line number Diff line change
Expand Up @@ -1143,7 +1143,7 @@ Notebook[
],
Cell[
StyleData["ChatStyleSheetInformation"],
TaggingRules -> <|"StyleSheetVersion" -> "1.2.2.3906691619"|>
TaggingRules -> <|"StyleSheetVersion" -> "1.2.4.3907141550"|>
],
Cell[
StyleData["Text"],
Expand Down Expand Up @@ -1530,6 +1530,7 @@ Notebook[
StyleDefinitions -> StyleData["Text"]
],
CellFrame -> 2,
TaggingRules -> <|"ChatNotebookSettings" -> <||>|>,
ShowCellLabel -> False,
CellFrameMargins -> {{12, 25}, {8, 8}},
CellFrameColor -> RGBColor[0.92549, 0.941176, 0.960784],
Expand Down Expand Up @@ -1803,6 +1804,7 @@ Notebook[
CellMargins -> {{66, 25}, {12, 5}},
CellElementSpacings -> {"CellMinHeight" -> 0, "ClosedCellHeight" -> 0},
CellGroupingRules -> "OutputGrouping",
TaggingRules -> <|"ChatNotebookSettings" -> <||>|>,
CellTrayWidgets -> <|
"ChatWidget" -> <|"Visible" -> False|>,
"ChatFeedback" -> <|
Expand Down Expand Up @@ -2730,12 +2732,14 @@ Notebook[
Hold[
With[ { cell$ = EvaluationCell[] },
{root$ = ParentCell[cell$]},
NotebookDelete[cell$];
Quiet[Needs["Wolfram`Chatbook`" -> None]];

Symbol["Wolfram`Chatbook`ChatbookAction"][
"ExplodeInPlace",
root$
]
];

NotebookDelete[cell$];
]
]
},
Expand All @@ -2750,12 +2754,14 @@ Notebook[
Hold[
With[ { cell$ = EvaluationCell[] },
{root$ = ParentCell[cell$]},
NotebookDelete[cell$];
Quiet[Needs["Wolfram`Chatbook`" -> None]];

Symbol["Wolfram`Chatbook`ChatbookAction"][
"ExplodeDuplicate",
root$
]
];

NotebookDelete[cell$];
]
]
},
Expand All @@ -2773,12 +2779,14 @@ Notebook[
Hold[
With[ { cell$ = EvaluationCell[] },
{root$ = ParentCell[cell$]},
NotebookDelete[cell$];
Quiet[Needs["Wolfram`Chatbook`" -> None]];

Symbol["Wolfram`Chatbook`ChatbookAction"][
"CopyExplodedCells",
root$
]
];

NotebookDelete[cell$];
]
]
},
Expand All @@ -2794,12 +2802,14 @@ Notebook[
Hold[
With[ { cell$ = EvaluationCell[] },
{root$ = ParentCell[cell$]},
NotebookDelete[cell$];
Quiet[Needs["Wolfram`Chatbook`" -> None]];

Symbol["Wolfram`Chatbook`ChatbookAction"][
"ToggleFormatting",
root$
]
];

NotebookDelete[cell$];
]
]
},
Expand All @@ -2814,12 +2824,14 @@ Notebook[
Hold[
With[ { cell$ = EvaluationCell[] },
{root$ = ParentCell[cell$]},
NotebookDelete[cell$];
Quiet[Needs["Wolfram`Chatbook`" -> None]];

Symbol["Wolfram`Chatbook`ChatbookAction"][
"CopyChatObject",
root$
]
];

NotebookDelete[cell$];
]
]
},
Expand Down
2 changes: 1 addition & 1 deletion PacletInfo.wl
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
PacletObject[ <|
"Name" -> "Wolfram/Chatbook",
"PublisherID" -> "Wolfram",
"Version" -> "1.2.3",
"Version" -> "1.2.4",
"WolframVersion" -> "13.3+",
"Description" -> "Wolfram Notebooks + LLMs",
"License" -> "MIT",
Expand Down
2 changes: 2 additions & 0 deletions Source/Chatbook/Common.wl
Original file line number Diff line number Diff line change
Expand Up @@ -130,6 +130,8 @@ KeyValueMap[ Function[ MessageName[ Chatbook, #1 ] = #2 ], <|
"RateLimitReached" -> "Rate limit reached for requests. Please try again later.",
"ResourceNotFound" -> "Resource `1` not found.",
"ResourceNotInstalled" -> "The resource `1` is not installed.",
"ServerMessageHeader" -> "The server responded with the following message: \n\n",
"ServerMessageTemplate" -> "The server responded with the following message: \n\n`1`",
"ServerOverloaded" -> "The server is currently overloaded with other requests. Please try again later.",
"ToolNotFound" -> "Tool `1` not found.",
"UnknownResponse" -> "Unexpected response from server",
Expand Down
18 changes: 5 additions & 13 deletions Source/Chatbook/FrontEnd.wl
Original file line number Diff line number Diff line change
Expand Up @@ -246,18 +246,7 @@ CurrentChatSettings[ args___ ] :=
(* ::**************************************************************************************************************:: *)
(* ::Subsection::Closed:: *)
(*$currentEvaluationObject*)

(* During asynchronous tasks, EvaluationCell[ ] will return $Failed, so we instead use this to take the first FE object
in ascending order of inheritance that we can read settings from. *)
$currentEvaluationObject := FirstCase[
Unevaluated @ {
EvaluationCell[ ],
EvaluationNotebook[ ],
$FrontEndSession
},
obj_ :> With[ { res = obj }, res /; MatchQ[ res, $$feObj ] ],
throwInternalFailure @ $currentEvaluationObject
];
$currentEvaluationObject := $FrontEndSession;

(* ::**************************************************************************************************************:: *)
(* ::Subsection::Closed:: *)
Expand Down Expand Up @@ -305,7 +294,10 @@ verifyInheritance0 // endDefinition;
inheritingQ // beginDefinition;

inheritingQ[ obj: $$feObj ] :=
TrueQ @ AbsoluteCurrentValue[ obj, { TaggingRules, "ChatNotebookSettings", "InheritanceTest" } ];
TrueQ @ Replace[
AbsoluteCurrentValue[ obj, { TaggingRules, "ChatNotebookSettings", "InheritanceTest" } ],
$Failed -> True
];

inheritingQ // endDefinition;

Expand Down
6 changes: 3 additions & 3 deletions Source/Chatbook/Menus.wl
Original file line number Diff line number Diff line change
Expand Up @@ -74,9 +74,9 @@ menuItem[ icon_, label_, action_String ] :=
Hold @ With[
{ $CellContext`cell = EvaluationCell[ ] },
{ $CellContext`root = ParentCell @ $CellContext`cell },
NotebookDelete @ $CellContext`cell;
Quiet @ Needs[ "Wolfram`Chatbook`" -> None ];
Symbol[ "Wolfram`Chatbook`ChatbookAction" ][ action, $CellContext`root ]
Symbol[ "Wolfram`Chatbook`ChatbookAction" ][ action, $CellContext`root ];
NotebookDelete @ $CellContext`cell;
]
];

Expand All @@ -88,8 +88,8 @@ menuItem[ icon_, label_, None ] :=
icon,
label,
Hold[
MessageDialog[ "Not Implemented" ];
NotebookDelete @ EvaluationCell[ ];
MessageDialog[ "Not Implemented" ]
]
];

Expand Down
141 changes: 97 additions & 44 deletions Source/Chatbook/SendChat.wl
Original file line number Diff line number Diff line change
Expand Up @@ -722,31 +722,59 @@ checkResponse // endDefinition;
(*writeResult*)
writeResult // beginDefinition;

writeResult[ settings_, container_, cell_, as_Association ] :=
Module[ { log, chunks, folded, body, data },
writeResult[ settings_, container_, cell_, as_Association ] := Enclose[
Module[ { log, body, data },

log = ConfirmMatch[ Internal`BagPart[ $debugLog, All ], { ___Association }, "DebugLog" ];
{ body, data } = ConfirmMatch[ extractBodyData @ log, { _, _ }, "ExtractBodyData" ];

If[ MatchQ[ as[ "StatusCode" ], Except[ 200, _Integer ] ] || AssociationQ @ data,
writeErrorCell[ cell, $badResponse = Association[ as, "Body" -> body, "BodyJSON" -> data ] ],
writeReformattedCell[ settings, container, cell ]
]
],
throwInternalFailure[ writeResult[ settings, container, cell, as ], ## ] &
];

writeResult // endDefinition;

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

extractBodyData[ log_List ] := Enclose[
Catch @ Module[ { chunks, folded, data },

FirstCase[
Reverse @ log,
KeyValuePattern[ "BodyChunk" -> body: Except[ "", _String ] ] :>
With[ { json = Quiet @ Developer`ReadRawJSONString @ body },
Throw @ { body, json } /; AssociationQ @ json
]
];

log = Internal`BagPart[ $debugLog, All ];
chunks = Cases[ log, KeyValuePattern[ "BodyChunk" -> s: Except[ "", _String ] ] :> s ];
folded = Fold[ StringJoin, chunks ];
data = Quiet @ Developer`ReadRawJSONString @ folded;

If[ AssociationQ @ data, Throw @ { folded, data } ];

{ body, data } = FirstCase[
FirstCase[
Flatten @ StringCases[
folded,
(StartOfString|"\n") ~~ "data: " ~~ s: Except[ "\n" ].. ~~ "\n" :> s
],
s_String :> With[ { json = Quiet @ Developer`ReadRawJSONString @ s },
{ s, json } /; MatchQ[ json, KeyValuePattern[ "error" -> _ ] ]
],
{ Last[ folded, Missing[ "NotAvailable" ] ], Missing[ "NotAvailable" ] }
];

If[ MatchQ[ as[ "StatusCode" ], Except[ 200, _Integer ] ] || AssociationQ @ data,
writeErrorCell[ cell, $badResponse = Association[ as, "Body" -> body, "BodyJSON" -> data ] ],
writeReformattedCell[ settings, container, cell ]
{ folded, Missing[ "NotAvailable" ] }
]
];
],
throwInternalFailure[ extractBodyData @ log, ## ] &
];

writeResult // endDefinition;
extractBodyData // endDefinition;

(* ::**************************************************************************************************************:: *)
(* ::Section::Closed:: *)
Expand Down Expand Up @@ -1887,8 +1915,11 @@ errorCell[ as_ ] :=
},
"Text",
"ChatOutput",
CellAutoOverwrite -> True,
CellTrayWidgets -> <| "ChatFeedback" -> <| "Visible" -> False |> |>,
CodeAssistOptions -> { "AutoDetectHyperlinks" -> True },
GeneratedCell -> True,
CellAutoOverwrite -> True
Initialization -> None
];

errorCell // endDefinition;
Expand All @@ -1898,47 +1929,69 @@ errorCell // endDefinition;
(*errorText*)
errorText // ClearAll;

errorText[ KeyValuePattern[ "BodyJSON" -> KeyValuePattern[ "error" -> KeyValuePattern[ "message" -> s_String ] ] ] ] :=
errorText @ s;
errorText[ KeyValuePattern[ "BodyJSON" -> json_ ] ] :=
With[ { text = errorText0 @ json },
text /; StringQ @ text || MatchQ[ text, $$textDataList ]
];

errorText[ str_String ] /; StringMatchQ[ str, "The model: `" ~~ __ ~~ "` does not exist" ] :=
Module[ { model, link, help, message },
errorText[ KeyValuePattern[
"BodyJSON" -> KeyValuePattern[ "Error"|"error" -> KeyValuePattern[ "Message"|"message" -> text_String ] ]
] ] := serverMessageTextData @ text;

model = StringReplace[ str, "The model: `" ~~ m__ ~~ "` does not exist" :> m ];
link = textLink[ "here", "https://platform.openai.com/docs/models/overview" ];
help = { " Click ", link, " for information about available models." };
errorText[ str_String ] := str;
errorText[ failure_Failure ] := ToString @ failure[ "Message" ];
errorText[ ___ ] := "An unexpected error occurred.";

message = If[ MemberQ[ getModelList[ ], model ],
"The specified API key does not have access to the model \"" <> model <> "\".",
"The model \"" <> model <> "\" does not exist or the specified API key does not have access to it."
];

Flatten @ { message, help }
];
(* Overrides for server messages can be defined here: *)
errorText0 // ClearAll;

(*
Note the subtle difference here where `model` is not followed by a colon.
This is apparently the best way we can determine the difference between a model that exists but isn't revealed
to the user and one that actually does not exist. Yes, this is ugly and will eventually be wrong.
*)
errorText[ str_String ] /; StringMatchQ[ str, "The model `" ~~ __ ~~ "` does not exist" ] :=
Module[ { model, link, help, message },
errorText0[ KeyValuePattern[ "Error"|"error" -> error_Association ] ] :=
errorText0 @ error;

model = StringReplace[ str, "The model `" ~~ m__ ~~ "` does not exist" :> m ];
link = textLink[ "here", "https://platform.openai.com/docs/models/overview" ];
help = { " Click ", link, " for information about available models." };
errorText0[ as: KeyValuePattern @ { "Code"|"code" -> code_, "Message"|"message" -> message_ } ] :=
errorText0[ as, code, message ];

message = If[ MemberQ[ getModelList[ ], model ],
"The specified API key does not have access to the model \"" <> model <> "\".",
"The model \"" <> model <> "\" does not exist."
];
errorText0[ as: KeyValuePattern @ { "Message"|"message" -> message_ } ] :=
errorText0[ as, None, message ];

Flatten @ { message, help }
errorText0[ as_, "model_not_found", message_String ] :=
Module[ { link, help },
If[ StringContainsQ[ message, "https://"|"http://" ],
serverMessageTextData @ message,
link = textLink[ "here", "https://platform.openai.com/docs/models/overview" ];
help = { " Click ", link, " for information about available models." };
Flatten @ {
StringReplace[
StringTrim[ message, "." ] <> ".",
"`" ~~ model: Except[ "`" ].. ~~ "`" :> "\""<>model<>"\""
],
help
}
]
];

errorText[ str_String ] := str;
errorText[ failure_Failure ] := ToString @ failure[ "Message" ];
errorText[ ___ ] := "An unexpected error occurred.";
errorText0[ as_, "context_length_exceeded", message_String ] :=
StringReplace[
message,
"Please reduce the length of the messages." ->
"Try using chat delimiters in order to reduce the total size of conversations."
];

errorText0[ as_, code_, message_String ] :=
serverMessageTextData @ message;

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

serverMessageTextData[ textData: _String | $$textDataList ] := Flatten @ {
Chatbook::ServerMessageHeader,
StyleBox[ #, FontOpacity -> 0.75, FontSlant -> Italic ] & /@ Flatten @ { textData }
};

serverMessageTextData // endDefinition;

(* ::**************************************************************************************************************:: *)
(* ::Subsubsubsection::Closed:: *)
Expand Down
Loading

0 comments on commit 78a8d8e

Please sign in to comment.