Skip to content

Commit

Permalink
Merge pull request #478 from WolframResearch/main
Browse files Browse the repository at this point in the history
Release v1.3.2
  • Loading branch information
rhennigan authored Nov 30, 2023
2 parents f7f8dff + f12bfa4 commit 242740a
Show file tree
Hide file tree
Showing 7 changed files with 189 additions and 68 deletions.
5 changes: 3 additions & 2 deletions PacletInfo.wl
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
PacletObject[ <|
"Name" -> "Wolfram/Chatbook",
"PublisherID" -> "Wolfram",
"Version" -> "1.3.1",
"Version" -> "1.3.2",
"WolframVersion" -> "13.3+",
"Description" -> "Wolfram Notebooks + LLMs",
"License" -> "MIT",
Expand All @@ -11,7 +11,8 @@ PacletObject[ <|
"ReleaseDate" -> "$RELEASE_DATE$",
"ReleaseURL" -> "$RELEASE_URL$",
"ActionURL" -> "$ACTION_URL$",
"Loading" -> "Startup",
"CommitURL" -> "$COMMIT_URL$",
"Loading" -> "Startup",
"PrimaryContext" -> "Wolfram`Chatbook`",
"Extensions" -> {
(* NOTE: The BeginStartup and EndStartup contexts are special, and need to
Expand Down
80 changes: 44 additions & 36 deletions Scripts/Common.wl
Original file line number Diff line number Diff line change
Expand Up @@ -107,6 +107,13 @@ messageString[ ___ ] := "-- Message text not found --";
(* ::Section::Closed:: *)
(*Definitions*)

$envSHA = SelectFirst[
{ Environment[ "GITHUB_SHA" ], Environment[ "BUILD_VCS_NUMBER_WolframLanguage_Paclets_Chatbook_PacChatbook" ] },
StringQ
];

$inCICD = StringQ @ $envSHA;

(* ::**************************************************************************************************************:: *)
(* ::Subsection::Closed:: *)
(*gitCommand*)
Expand All @@ -124,24 +131,24 @@ gitCommand[ cmd_ ] := gitCommand[ cmd, Directory[ ] ];
(* ::**************************************************************************************************************:: *)
(* ::Subsection::Closed:: *)
(*releaseID*)
releaseID[ dir_ ] :=
With[ { sha = Environment[ "GITHUB_SHA" ] },
If[ StringQ @ sha,
sha,
gitCommand[ { "rev-parse", "HEAD" }, dir ]
]
];
releaseID[ dir_ ] := FirstCase[
Unevaluated @ { $envSHA, gitCommand[ { "rev-parse", "HEAD" }, dir ] },
expr_ :> With[ { id = expr }, id /; StringQ @ id ],
"None"
];

(* ::**************************************************************************************************************:: *)
(* ::Subsection::Closed:: *)
(*releaseURL*)
releaseURL[ file_ ] :=
releaseURL[ file_ ] := Enclose[
Enclose @ Module[ { pac, repo, ver },
pac = PacletObject @ Flatten @ File @ file;
repo = ConfirmBy[ Environment[ "GITHUB_REPOSITORY" ], StringQ ];
ver = ConfirmBy[ pac[ "Version" ], StringQ ];
TemplateApply[ "https://github.com/`1`/releases/tag/v`2`", { repo, ver } ]
];
],
"None" &
];

(* ::**************************************************************************************************************:: *)
(* ::Subsection::Closed:: *)
Expand All @@ -154,42 +161,47 @@ actionURL[ ] := Enclose[
runID = cs @ Environment[ "GITHUB_RUN_ID" ];
cs @ URLBuild @ { domain, repo, "actions", "runs", runID }
],
"$ACTION_URL$" &
"None" &
];

(* ::**************************************************************************************************************:: *)
(* ::Subsection::Closed:: *)
(*updatePacletInfo*)
updatePacletInfo[ dir_ ] /; StringQ @ Environment[ "GITHUB_ACTION" ] := Enclose[
updatePacletInfo[ dir_ ] /; $inCICD := Enclose[
Module[
{ cs, file, string, id, date, url, run, cmt, new },

cs = ConfirmBy[ #, StringQ ] &;
file = cs @ FileNameJoin @ { dir, "PacletInfo.wl" };
string = cs @ ReadString @ file;
id = cs @ releaseID @ dir;
date = cs @ DateString[ "ISODateTime", TimeZone -> 0 ];
cs = ConfirmBy[ Echo[ #1, "Update PacletInfo [" <> ToString @ #2 <> "]: " ], StringQ, #2 ] &;
file = cs[ FileNameJoin @ { dir, "PacletInfo.wl" }, "Original PacletInfo" ];
string = cs[ ReadString @ file, "ReadString" ];
id = cs[ releaseID @ dir, "ReleaseID" ];
date = cs[ DateString[ "ISODateTime", TimeZone -> 0 ], "Timestamp" ];
date = StringTrim[ date, "Z" ] <> "Z";
url = cs @ releaseURL @ file;
run = cs @ actionURL[ ];
cmt = cs @ commitURL @ id;

new = cs @ StringReplace[
string,
{
"\r\n" -> "\n",
"$RELEASE_ID$" -> id,
"$RELEASE_DATE$" -> date,
"$RELEASE_URL$" -> url,
"$ACTION_URL$" -> run
}
url = cs[ releaseURL @ file, "ReleaseURL" ];
run = cs[ actionURL[ ], "ActionURL" ];
cmt = cs[ commitURL @ id, "CommitURL" ];

new = cs[
StringReplace[
string,
{
"\r\n" -> "\n",
"$RELEASE_ID$" -> id,
"$RELEASE_DATE$" -> date,
"$RELEASE_URL$" -> url,
"$ACTION_URL$" -> run,
"$COMMIT_URL$" -> cmt
}
],
"Updated PacletInfo"
];

Print[ "Updating PacletInfo" ];
Print[ " ReleaseID: ", id ];
Print[ " ReleaseDate: ", date ];
Print[ " ReleaseURL: ", url ];
Print[ " ActionURL: ", run ];
Print[ " CommitURL: ", cmt ];

Confirm @ WithCleanup[ BinaryWrite[ file, new ],
Close @ file
Expand All @@ -200,7 +212,8 @@ updatePacletInfo[ dir_ ] /; StringQ @ Environment[ "GITHUB_ACTION" ] := Enclose[
],
Function[
Print[ "::error::Failed to update PacletInfo template parameters." ];
Exit[ 1 ]
Print[ " ", ToString[ #, InputForm ] ];
If[ StringQ @ Environment[ "GITHUB_ACTION" ], Exit[ 1 ] ]
]
];

Expand All @@ -224,12 +237,7 @@ updateReleaseInfoCell[ dir_, url_, cmt_, run_ ] /;
];


commitURL[ sha_String ] := Enclose @ URLBuild @ {
"https://github.com",
ConfirmBy[ Environment[ "GITHUB_REPOSITORY" ], StringQ ],
"commit",
sha
};
commitURL[ sha_String ] := URLBuild @ { "https://github.com/WolframResearch/Chatbook/commit", sha };


releaseInfoCell[ release_, commit_, run_ ] := Enclose[
Expand Down
9 changes: 7 additions & 2 deletions Source/Chatbook/Actions.wl
Original file line number Diff line number Diff line change
Expand Up @@ -666,8 +666,13 @@ revertMultimodalContent // beginDefinition;
revertMultimodalContent[ messages_List ] :=
revertMultimodalContent /@ messages;

revertMultimodalContent[ as: KeyValuePattern[ "Content" -> content_List ] ] :=
<| as, "Content" -> StringJoin @ Select[ content, StringQ ] |>;
revertMultimodalContent[ as: KeyValuePattern[ "Content" -> content_List ] ] := <|
as,
"Content" -> StringJoin @ Cases[
content,
s_String | KeyValuePattern @ { "Type" -> "Text", "Data" -> s_String } :> s
]
|>;

revertMultimodalContent[ as: KeyValuePattern[ "Content" -> _String ] ] :=
as;
Expand Down
47 changes: 43 additions & 4 deletions Source/Chatbook/ChatMessages.wl
Original file line number Diff line number Diff line change
Expand Up @@ -386,7 +386,7 @@ tokenCount // endDefinition;
applyTokenizer // beginDefinition;
applyTokenizer[ tokenizer_, content_String ] := tokenizer @ content;
applyTokenizer[ tokenizer_, content_? graphicsQ ] := tokenizer @ content;
applyTokenizer[ tokenizer_, content_List ] := Flatten[ tokenizer /@ content ];
applyTokenizer[ tokenizer_, content_List ] := Flatten[ applyTokenizer[ tokenizer, # ] & /@ content ];
applyTokenizer[ tokenizer_, KeyValuePattern[ "Data" -> data_ ] ] := tokenizer @ data;
applyTokenizer // endDefinition;

Expand Down Expand Up @@ -658,7 +658,7 @@ makeMessageContent // endDefinition;
expandMultimodalString // beginDefinition;

expandMultimodalString[ string_String ] /; $multimodalMessages := Enclose[
Module[ { split, joined },
Module[ { split, joined, typed },

split = Flatten @ StringSplit[
string,
Expand All @@ -675,8 +675,9 @@ expandMultimodalString[ string_String ] /; $multimodalMessages := Enclose[
}
];

joined = FixedPoint[ Replace[ { a___, b_String, c_String, d___ } :> { a, b<>c, d } ], split ];
Replace[ joined, { msg_String } :> msg ]
joined = Flatten @ Replace[ SplitBy[ split, StringQ ], s: { _String, ___ } :> StringJoin @ s, { 1 } ];
typed = ConfirmMatch[ inferMultimodalTypes @ joined, { ___? AssociationQ } | { ___? StringQ }, "Typed" ];
Replace[ typed, { msg_String } :> msg ]
],
throwInternalFailure[ expandMultimodalString @ string, ## ] &
];
Expand All @@ -686,6 +687,44 @@ expandMultimodalString[ string_String ] :=

expandMultimodalString // endDefinition;

(* ::**************************************************************************************************************:: *)
(* ::Subsubsubsection::Closed:: *)
(*inferMultimodalTypes*)
inferMultimodalTypes // beginDefinition;

inferMultimodalTypes[ content_List ] := Enclose[
Module[ { typed },
typed = ConfirmMatch[ inferMultimodalTypes0 @ content, { ___? AssociationQ }, "Typed" ];
If[ MatchQ[ typed, { KeyValuePattern[ "Type" -> "Text" ] .. } ],
ConfirmMatch[ Lookup[ typed, "Data" ], { __String }, "TextData" ],
typed
]
],
throwInternalFailure
];

inferMultimodalTypes // endDefinition;

inferMultimodalTypes0 // beginDefinition;
inferMultimodalTypes0[ content_List ] := inferMultimodalTypes0 /@ content;
inferMultimodalTypes0[ content_String ] := <| "Type" -> "Text" , "Data" -> content |>;
inferMultimodalTypes0[ content_? graphicsQ ] := <| "Type" -> "Image", "Data" -> ensureCompatibleImage @ content |>;
inferMultimodalTypes0 // endDefinition;

(* ::**************************************************************************************************************:: *)
(* ::Subsubsubsection::Closed:: *)
(*ensureCompatibleImage*)
ensureCompatibleImage // beginDefinition;
ensureCompatibleImage[ img_ ] /; $useRasterizationCompatibility && ! Image`PossibleImageQ @ img := Rasterize @ img;
ensureCompatibleImage[ img_ ] := img;
ensureCompatibleImage // endDefinition;


$useRasterizationCompatibility := Enclose[
$useRasterizationCompatibility =
! PacletNewerQ[ ConfirmBy[ PacletObject[ "ServiceConnection_OpenAI" ], PacletObjectQ ], "13.3.18" ]
];

(* ::**************************************************************************************************************:: *)
(* ::Subsubsection::Closed:: *)
(*expressionURIQ*)
Expand Down
58 changes: 49 additions & 9 deletions Source/Chatbook/SendChat.wl
Original file line number Diff line number Diff line change
Expand Up @@ -673,12 +673,12 @@ withFETasks // endDefinition;
(*writeChunk*)
writeChunk // beginDefinition;

writeChunk[ container_, cell_, KeyValuePattern[ "BodyChunkProcessed" -> chunk_String ] ] :=
writeChunk0[ container, cell, chunk, chunk ];

writeChunk[ container_, cell_, KeyValuePattern[ "BodyChunkProcessed" -> { chunks___String } ] ] :=
With[ { chunk = StringJoin @ chunks },
writeChunk0[ container, cell, chunk, chunk ]
writeChunk[ container_, cell_, KeyValuePattern[ "BodyChunkProcessed" -> chunks_ ] ] :=
With[ { chunk = StringJoin @ Select[ Flatten @ { chunks }, StringQ ] },
If[ chunk === "",
Null,
writeChunk0[ container, cell, chunk, chunk ]
]
];

(* TODO: this definition is obsolete once LLMServices is widely available: *)
Expand Down Expand Up @@ -968,7 +968,7 @@ toolFreeQ // endDefinition;
toolEvaluation // beginDefinition;

toolEvaluation[ settings_, container_Symbol, cell_, as_Association ] := Enclose[
Module[ { string, callPos, toolCall, toolResponse, output, messages, newMessages, req, toolID },
Module[ { string, callPos, toolCall, toolResponse, output, messages, newMessages, req, toolID, task },

string = ConfirmBy[ container[ "FullContent" ], StringQ, "FullContent" ];

Expand Down Expand Up @@ -1010,7 +1010,18 @@ toolEvaluation[ settings_, container_Symbol, cell_, as_Association ] := Enclose[

appendToolResult[ container, output, toolID ];

$lastTask = chatSubmit[ container, req, cell, settings ]
task = $lastTask = chatSubmit[ container, req, cell, settings ];

addHandlerArguments[ "Task" -> task ];

CurrentValue[ cell, { TaggingRules, "ChatNotebookSettings", "CellObject" } ] = cell;
CurrentValue[ cell, { TaggingRules, "ChatNotebookSettings", "Task" } ] = task;

If[ FailureQ @ task, throwTop @ writeErrorCell[ cell, task ] ];

If[ task === $Canceled, StopChat @ cell ];

task
],
throwInternalFailure[ toolEvaluation[ settings, container, cell, as ], ## ] &
];
Expand Down Expand Up @@ -1356,10 +1367,39 @@ multimodalPacletsAvailable[ ] := multimodalPacletsAvailable[ ] = (
);

multimodalPacletsAvailable[ llmFunctions_PacletObject? PacletObjectQ, openAI_PacletObject? PacletObjectQ ] :=
TrueQ @ And[ PacletNewerQ[ llmFunctions, "1.2.4" ], PacletNewerQ[ openAI, "13.3.18" ] ];
TrueQ @ And[
PacletNewerQ[ llmFunctions, "1.2.4" ],
Or[ PacletNewerQ[ openAI, "13.3.18" ],
openAI[ "Version" ] === "13.3.18" && multimodalOpenAIQ @ openAI
]
];

multimodalPacletsAvailable // endDefinition;

(* ::**************************************************************************************************************:: *)
(* ::Subsubsubsection::Closed:: *)
(*multimodalOpenAIQ*)
multimodalOpenAIQ // beginDefinition;

multimodalOpenAIQ[ openAI_PacletObject ] := Enclose[
Catch @ Module[ { dir, file, multimodal },

dir = ConfirmBy[ openAI[ "Location" ], DirectoryQ, "Location" ];
file = ConfirmBy[ FileNameJoin @ { dir, "Kernel", "OpenAI.m" }, FileExistsQ, "File" ];

multimodal = WithCleanup[
Quiet @ Close @ file,
ConfirmMatch[ Find[ file, "data:image/jpeg;base64," ], _String? StringQ | EndOfFile, "Find" ],
Quiet @ Close @ file
];

StringQ @ multimodal
],
throwInternalFailure
];

multimodalOpenAIQ // endDefinition;

(* ::**************************************************************************************************************:: *)
(* ::Subsubsection::Closed:: *)
(*getLLMEvaluator*)
Expand Down
Loading

0 comments on commit 242740a

Please sign in to comment.