From cf828e4c184162e8b5620948ae486ae4a9c04305 Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Fri, 17 Nov 2023 08:49:43 -0500 Subject: [PATCH 01/50] Utility functions to populate model selection menu --- Source/Chatbook/Services.wl | 76 +++++++++++++++++++++++++++++++++++-- 1 file changed, 72 insertions(+), 4 deletions(-) diff --git a/Source/Chatbook/Services.wl b/Source/Chatbook/Services.wl index b7cce46c..e83d7250 100644 --- a/Source/Chatbook/Services.wl +++ b/Source/Chatbook/Services.wl @@ -9,6 +9,7 @@ HoldComplete[ `$enableLLMServices; `$servicesLoaded; `$useLLMServices; + `getLLMServicesModelList; ]; Begin[ "`Private`" ]; @@ -17,6 +18,8 @@ Needs[ "Wolfram`Chatbook`" ]; Needs[ "Wolfram`Chatbook`Common`" ]; Needs[ "Wolfram`Chatbook`Models`" ]; +$ContextAliases[ "llm`" ] = "LLMServices`"; + (* ::**************************************************************************************************************:: *) (* ::Section::Closed:: *) (*Configuration*) @@ -33,6 +36,71 @@ $llmServicesAvailable := $llmServicesAvailable = ( (* ::Section::Closed:: *) (*Available Services*) +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*$availableServiceNames*) +$availableServiceNames := getAvailableServiceNames[ ]; + +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*getAvailableServiceNames*) +getAvailableServiceNames // beginDefinition; +getAvailableServiceNames[ ] := getAvailableServiceNames @ $useLLMServices; +getAvailableServiceNames[ False ] := Keys @ $fallBackServices; +getAvailableServiceNames[ True ] := getAvailableServiceNames0[ ]; +getAvailableServiceNames // endDefinition; + + +getAvailableServiceNames0 // beginDefinition; + +getAvailableServiceNames0[ ] := ( + PacletInstall[ "Wolfram/LLMFunctions" ]; + Needs[ "LLMServices`" -> None ]; + getAvailableServiceNames0 @ llm`LLMServiceInformation @ llm`ChatSubmit +); + +getAvailableServiceNames0[ services_Association ] := + Keys @ services; + +getAvailableServiceNames0 // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*getServiceModels*) +getServiceModelList // beginDefinition; + +getServiceModelList[ name_String ] := + getServiceModelList[ name, llm`LLMServiceInformation[ llm`ChatSubmit, name ] ]; + +getServiceModelList[ name_String, info_Association ] := + getServiceModelList[ name, info, getModelListQuietly @ info ]; + +getServiceModelList[ name_, info_, Missing[ "NotConnected" ] ] := + Missing[ "NotConnected" ]; + +getServiceModelList[ "OpenAI", info_, models: { "gpt-4", "gpt-3.5-turbo-0613" } ] := + With[ { full = getOpenAIChatModels[ ] }, + getServiceModelList[ "OpenAI", info, full ] /; MatchQ[ full, Except[ models, { __String } ] ] + ]; + +getServiceModelList[ name_String, info_, models: { ___String } ] := + getServiceModelList[ name ] = <| "Service" -> name, "Name" -> #1 |> & /@ models; + +getServiceModelList // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*getModelListQuietly*) +getModelListQuietly // beginDefinition; + +(* cSpell: ignore nprmtv, genconerr, invs, nolink *) +getModelListQuietly[ info_Association ] := Quiet[ + Check[ info[ "ModelList" ], Missing[ "NotConnected" ], DialogInput::nprmtv ], + { DialogInput::nprmtv, ServiceConnect::genconerr, ServiceConnect::invs, ServiceExecute::nolink } +]; + +getModelListQuietly // endDefinition; + (* ::**************************************************************************************************************:: *) (* ::Subsection::Closed:: *) (*$availableServices*) @@ -52,19 +120,19 @@ getAvailableServices0 // beginDefinition; getAvailableServices0[ ] := ( PacletInstall[ "Wolfram/LLMFunctions" ]; Needs[ "LLMServices`" -> None ]; - getAvailableServices0 @ LLMServices`LLMServiceInformation[ LLMServices`ChatSubmit, "Services" ] + getAvailableServices0 @ llm`LLMServiceInformation @ llm`ChatSubmit ); getAvailableServices0[ services0_Association? AssociationQ ] := Enclose[ Catch @ Module[ { services, withServiceName, withModels }, - services = Replace[ services0, <| |> :> $fallBackServices ]; + services = Replace[ services0, <| |> :> $fallBackServices ]; withServiceName = Association @ KeyValueMap[ #1 -> <| "ServiceName" -> #1, #2 |> &, services ]; withModels = Replace[ withServiceName, - as: KeyValuePattern @ { "ServiceName" -> service_String, "ModelList" -> func_ } :> - RuleCondition @ With[ { models = func[ ] }, + as: KeyValuePattern @ { "ServiceName" -> service_String } :> + RuleCondition @ With[ { models = getServiceModelList @ service }, If[ ListQ @ models, (* workaround for KeyValuePattern bug *) <| as, "Models" -> standardizeModelData[ service, models ] |>, as From 800edda98c72afd9e6b19df760468934d1d71101 Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Tue, 5 Dec 2023 15:57:15 -0500 Subject: [PATCH 02/50] Created submenus for models returned by LLMServices --- Source/Chatbook/Common.wl | 12 +- Source/Chatbook/Menus.wl | 259 +++++++++++++++++----------- Source/Chatbook/Models.wl | 4 +- Source/Chatbook/Services.wl | 20 ++- Source/Chatbook/Settings.wl | 7 +- Source/Chatbook/UI.wl | 324 +++++++++++++++++++++++++----------- 6 files changed, 416 insertions(+), 210 deletions(-) diff --git a/Source/Chatbook/Common.wl b/Source/Chatbook/Common.wl index 5c854554..1429776c 100644 --- a/Source/Chatbook/Common.wl +++ b/Source/Chatbook/Common.wl @@ -31,6 +31,7 @@ BeginPackage[ "Wolfram`Chatbook`Common`" ]; `$$textData; `$$textDataList; `$$unspecified; +`$$feObj; `$catchTopTag; `beginDefinition; @@ -107,9 +108,14 @@ $$nestedCellStyle = cellStylePattern @ $nestedCellStyles; $$textDataItem = (_String|_Cell|_StyleBox|_ButtonBox); $$textDataList = { $$textDataItem... }; $$textData = $$textDataItem | $$textDataList; -$$optionsSequence = (Rule|RuleDelayed)[ _Symbol|_String, _ ] ...; -$$size = Infinity | (_Real|_Integer)? NonNegative; -$$unspecified = _Missing | Automatic | Inherited; + +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*Other Argument Patterns *) +$$optionsSequence = (Rule|RuleDelayed)[ _Symbol|_String, _ ] ...; +$$size = Infinity | (_Real|_Integer)? NonNegative; +$$unspecified = _Missing | Automatic | Inherited; +$$feObj = _FrontEndObject | $FrontEndSession | _NotebookObject | _CellObject | _BoxObject; (* ::**************************************************************************************************************:: *) (* ::Section::Closed:: *) diff --git a/Source/Chatbook/Menus.wl b/Source/Chatbook/Menus.wl index 48edc471..6eaf81e2 100644 --- a/Source/Chatbook/Menus.wl +++ b/Source/Chatbook/Menus.wl @@ -3,141 +3,198 @@ *) -BeginPackage["Wolfram`Chatbook`Menus`"] +(* ::Section::Closed:: *) +(*Package Header*) +BeginPackage[ "Wolfram`Chatbook`Menus`" ]; -Needs["GeneralUtilities`" -> None] +(* :!CodeAnalysis::BeginBlock:: *) + +HoldComplete[ + `AttachSubmenu; + `MakeMenu; + `removeChatMenus; +]; + +Needs[ "GeneralUtilities`" -> None ]; GeneralUtilities`SetUsage[MakeMenu, " MakeMenu[$$] returns an expression representing a menu of actions. The generated menu expression may depend on styles from the Chatbook stylesheet. -"] +"]; GeneralUtilities`SetUsage[AttachSubmenu, " AttachSubmenu[parentMenu$, submenu$] attaches submenu$ to parentMenu$, taking care to attach to the left or right side based on heuristic for available space. -"] +"]; + +Begin[ "`Private`" ]; + +Needs[ "Wolfram`Chatbook`Common`" ]; +Needs[ "Wolfram`Chatbook`ErrorUtils`" ]; +Needs[ "Wolfram`Chatbook`FrontEnd`" ]; -Begin["`Private`"] +(* ::**************************************************************************************************************:: *) +(* ::Section::Closed:: *) +(*MakeMenu*) +MakeMenu // beginDefinition; -Needs["Wolfram`Chatbook`Common`"] -Needs["Wolfram`Chatbook`ErrorUtils`"] +MakeMenu[ items_List ] := + MakeMenu[ items, Automatic ]; -(*========================================================*) +MakeMenu[ items_List, frameColor_ ] := + MakeMenu[ items, frameColor, Automatic ]; -SetFallthroughError[MakeMenu] +MakeMenu[ items_List, Automatic, width_ ] := + MakeMenu[ items, GrayLevel[ 0.85 ], width ]; -MakeMenu[ - items_List, - frameColor_, - width_ -] := - Pane[ - RawBoxes @ TemplateBox[ - { - ToBoxes @ Column[ menuItem /@ items, ItemSize -> Automatic, Spacings -> 0, Alignment -> Left ], - FrameMargins -> 3, - Background -> GrayLevel[ 0.98 ], - RoundingRadius -> 3, - FrameStyle -> Directive[ AbsoluteThickness[ 1 ], frameColor ], - ImageMargins -> 0 - }, - "Highlighted" - ], - ImageSize -> { width, Automatic } - ]; +MakeMenu[ items_List, frameColor_, Automatic ] := + MakeMenu[ items, frameColor, 200 ]; -(*====================================*) +MakeMenu[ items_List, frameColor_, width_ ] := + Pane[ + RawBoxes @ TemplateBox[ + { + ToBoxes @ Column[ menuItem /@ items, ItemSize -> Automatic, Spacings -> 0, Alignment -> Left ], + Background -> GrayLevel[ 0.98 ], + FrameMargins -> 3, + FrameStyle -> Directive[ AbsoluteThickness[ 1 ], frameColor ], + ImageMargins -> 0, + RoundingRadius -> 3 + }, + "Highlighted" + ], + ImageSize -> { width, Automatic } + ]; -SetFallthroughError[menuItem] +MakeMenu // endDefinition; -menuItem[ { args__ } ] := menuItem @ args; +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*menuItem*) +menuItem // beginDefinition; -menuItem[ Delimiter ] := RawBoxes @ TemplateBox[ { }, "ChatMenuItemDelimiter" ]; +menuItem[ { args__ } ] := + menuItem @ args; -menuItem[ label_ :> action_ ] := menuItem[Graphics[{}, ImageSize -> 0], label, Hold[action]] +menuItem[ Delimiter ] := + RawBoxes @ TemplateBox[ { }, "ChatMenuItemDelimiter" ]; -menuItem[ section_ ] := RawBoxes @ TemplateBox[ { ToBoxes @ section }, "ChatMenuSection" ]; +menuItem[ label_ :> action_ ] := + menuItem[ Graphics[ { }, ImageSize -> 0 ], label, Hold @ action ]; + +menuItem[ section_ ] := + RawBoxes @ TemplateBox[ { ToBoxes @ section }, "ChatMenuSection" ]; menuItem[ name_String, label_, code_ ] := - With[ { icon = chatbookIcon @ name }, - If[ MissingQ @ icon, - menuItem[ RawBoxes @ TemplateBox[ { name }, "ChatMenuItemToolbarIcon" ], label, code ], - menuItem[ icon, label, code ] - ] - ]; + With[ { icon = chatbookIcon @ name }, + If[ MissingQ @ icon, + menuItem[ RawBoxes @ TemplateBox[ { name }, "ChatMenuItemToolbarIcon" ], label, code ], + menuItem[ icon, label, code ] + ] + ]; menuItem[ icon_, label_, action_String ] := - menuItem[ - icon, - label, - Hold @ With[ - { $CellContext`cell = EvaluationCell[ ] }, - { $CellContext`root = ParentCell @ $CellContext`cell }, - Quiet @ Needs[ "Wolfram`Chatbook`" -> None ]; - Symbol[ "Wolfram`Chatbook`ChatbookAction" ][ action, $CellContext`root ]; - NotebookDelete @ $CellContext`cell; - ] - ]; + menuItem[ + icon, + label, + Hold @ With[ + { $CellContext`cell = EvaluationCell[ ] }, + { $CellContext`root = ParentCell @ $CellContext`cell }, + Quiet @ Needs[ "Wolfram`Chatbook`" -> None ]; + Symbol[ "Wolfram`Chatbook`ChatbookAction" ][ action, $CellContext`root ]; + NotebookDelete @ $CellContext`cell; + ] + ]; menuItem[ None, content_, None ] := - content; + content; menuItem[ icon_, label_, None ] := - menuItem[ - icon, - label, - Hold[ - MessageDialog[ "Not Implemented" ]; - NotebookDelete @ EvaluationCell[ ]; - ] - ]; + menuItem[ + icon, + label, + Hold[ + MessageDialog[ "Not Implemented" ]; + NotebookDelete @ EvaluationCell[ ]; + ] + ]; menuItem[ icon_, label_, code_ ] := - RawBoxes @ TemplateBox[ { ToBoxes @ icon, ToBoxes @ label, code }, "ChatMenuItem" ]; - -(*========================================================*) - -AttachSubmenu[ - parentMenu_CellObject, - submenu_ -] := With[{ - mouseX = MousePosition["WindowScaled"][[1]] -}, { - (* Note: Depending on the X coordinate of the users mouse - when they click the 'Advanced Settings' button, either - show the attached submenu to the left or right of the - outer menu. This ensures that this submenu doesn't touch - the right edge of the notebook window when it is opened - from the 'Chat Settings' notebook toolbar. *) - positions = If[ - TrueQ[mouseX < 0.5], - { - {Right, Bottom}, - {Left, Bottom} - }, - { - {Left, Bottom}, - {Right, Bottom} - } - ] -}, - AttachCell[ - EvaluationCell[], - submenu, - positions[[1]], - {50, 50}, - positions[[2]], - RemovalConditions -> "MouseExit" - ] -] - -(*========================================================*) + RawBoxes @ TemplateBox[ { ToBoxes @ icon, ToBoxes @ label, code }, "ChatMenuItem" ]; + +menuItem // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Section::Closed:: *) +(*AttachSubmenu*) +AttachSubmenu[ parentMenu_, submenu: Cell[ __, "AttachedChatMenu", ___ ] ] := Enclose[ + Module[ { pos, oPos, offset }, + NotebookDelete @ Cells[ parentMenu, AttachedCell -> True, CellStyle -> "AttachedChatMenu" ]; + { pos, oPos } = ConfirmMatch[ determineAttachmentPosition[ ], { { _, _ }, { _, _ } }, "Position" ]; + offset = If[ MatchQ[ pos, { Left, _ } ], { -3, 0 }, { 3, 0 } ]; + AttachCell[ + parentMenu, + submenu, + pos, + Offset[ offset, { 0, 0 } ], + oPos, + RemovalConditions -> { "MouseClickOutside", "EvaluatorQuit" } + ] + ], + throwInternalFailure +]; + +AttachSubmenu[ parentMenu_, Cell[ boxes_, style__String, opts: OptionsPattern[ ] ] ] := + AttachSubmenu[ parentMenu, Cell[ boxes, style, "AttachedChatMenu", opts ] ]; + +AttachSubmenu[ parentMenu_, expr: Except[ _Cell ] ] := + AttachSubmenu[ parentMenu, Cell[ BoxData @ ToBoxes @ expr, "AttachedChatMenu" ] ]; + +AttachSubmenu[ expr_ ] := + AttachSubmenu[ EvaluationCell[ ], expr ]; + +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*determineAttachmentPosition*) +determineAttachmentPosition // beginDefinition; +determineAttachmentPosition[ ] := determineAttachmentPosition @ MousePosition[ "WindowScaled" ]; +determineAttachmentPosition[ pos_List ] := determineAttachmentPosition[ pos, quadrant @ pos ]; +determineAttachmentPosition[ _, { h_, v_ } ] := { { Replace[ h, { Left -> Right, Right -> Left } ], v }, { h, v } }; +determineAttachmentPosition // endDefinition; + +quadrant // beginDefinition; +quadrant[ { x_? NumberQ, y_? NumberQ } ] := quadrant[ TrueQ[ x >= 0.5 ], TrueQ[ y >= 0.5 ] ]; +quadrant[ True , True ] := { Right, Bottom }; +quadrant[ True , False ] := { Right, Top }; +quadrant[ False, True ] := { Left , Bottom }; +quadrant[ False, False ] := { Left , Top }; +quadrant // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Section::Closed:: *) +(*removeChatMenus*) +removeChatMenus // beginDefinition; + +removeChatMenus[ box_BoxObject ] := + removeChatMenus @ parentCell @ box; + +removeChatMenus[ cell_CellObject ] /; MemberQ[ cellStyles @ cell, "AttachedChatMenu" ] := + removeChatMenus @ parentCell @ cell; + +removeChatMenus[ cell_CellObject ] := + NotebookDelete @ Cells[ cell, AttachedCell -> True, CellStyle -> "AttachedChatMenu" ]; + +removeChatMenus // endDefinition; +(* ::**************************************************************************************************************:: *) +(* ::Section::Closed:: *) +(*Package Footer*) If[ Wolfram`ChatbookInternal`$BuildingMX, Null; ]; -End[] +(* :!CodeAnalysis::EndBlock:: *) -EndPackage[] \ No newline at end of file +End[ ]; +EndPackage[ ]; \ No newline at end of file diff --git a/Source/Chatbook/Models.wl b/Source/Chatbook/Models.wl index d1a38e7e..68059153 100644 --- a/Source/Chatbook/Models.wl +++ b/Source/Chatbook/Models.wl @@ -139,7 +139,7 @@ modelName // endDefinition; (*toModelName*) toModelName // beginDefinition; -toModelName[ KeyValuePattern @ { "Service" -> service_, "Model" -> model_ } ] := +toModelName[ KeyValuePattern @ { "Service" -> service_, "Name"|"Model" -> model_ } ] := toModelName @ { service, model }; toModelName[ { service_String, name_String } ] := toModelName @ name; @@ -300,7 +300,7 @@ standardizeModelData[ service_String, models_List ] := standardizeModelData[ service_String, model_ ] := With[ { as = standardizeModelData @ model }, - (standardizeModelData[ service, model ] = <| "ServiceName" -> service, as |>) /; AssociationQ @ as + (standardizeModelData[ service, model ] = <| "Service" -> service, as |>) /; AssociationQ @ as ]; standardizeModelData // endDefinition; diff --git a/Source/Chatbook/Services.wl b/Source/Chatbook/Services.wl index e83d7250..eaadba2e 100644 --- a/Source/Chatbook/Services.wl +++ b/Source/Chatbook/Services.wl @@ -9,7 +9,9 @@ HoldComplete[ `$enableLLMServices; `$servicesLoaded; `$useLLMServices; - `getLLMServicesModelList; + `getAvailableServiceNames; + `getServiceModelList; + `modelListCachedQ; ]; Begin[ "`Private`" ]; @@ -36,6 +38,13 @@ $llmServicesAvailable := $llmServicesAvailable = ( (* ::Section::Closed:: *) (*Available Services*) +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*modelListCachedQ*) +modelListCachedQ // beginDefinition; +modelListCachedQ[ name_String ] := False; +modelListCachedQ // endDefinition; + (* ::**************************************************************************************************************:: *) (* ::Subsection::Closed:: *) (*$availableServiceNames*) @@ -84,7 +93,10 @@ getServiceModelList[ "OpenAI", info_, models: { "gpt-4", "gpt-3.5-turbo-0613" } ]; getServiceModelList[ name_String, info_, models: { ___String } ] := - getServiceModelList[ name ] = <| "Service" -> name, "Name" -> #1 |> & /@ models; + WithCleanup[ + getServiceModelList[ name ] = standardizeModelData[ name, <| "Service" -> name, "Name" -> #1 |> & /@ models ], + modelListCachedQ[ name ] = True + ]; getServiceModelList // endDefinition; @@ -127,11 +139,11 @@ getAvailableServices0[ services0_Association? AssociationQ ] := Enclose[ Catch @ Module[ { services, withServiceName, withModels }, services = Replace[ services0, <| |> :> $fallBackServices ]; - withServiceName = Association @ KeyValueMap[ #1 -> <| "ServiceName" -> #1, #2 |> &, services ]; + withServiceName = Association @ KeyValueMap[ #1 -> <| "Service" -> #1, #2 |> &, services ]; withModels = Replace[ withServiceName, - as: KeyValuePattern @ { "ServiceName" -> service_String } :> + as: KeyValuePattern @ { "Service" -> service_String } :> RuleCondition @ With[ { models = getServiceModelList @ service }, If[ ListQ @ models, (* workaround for KeyValuePattern bug *) <| as, "Models" -> standardizeModelData[ service, models ] |>, diff --git a/Source/Chatbook/Settings.wl b/Source/Chatbook/Settings.wl index 54d6cbe3..3e36c89f 100644 --- a/Source/Chatbook/Settings.wl +++ b/Source/Chatbook/Settings.wl @@ -66,15 +66,14 @@ $defaultChatSettings = <| (* ::**************************************************************************************************************:: *) (* ::Subsection::Closed:: *) (*Argument Patterns*) -$$feObj = _FrontEndObject | $FrontEndSession | _NotebookObject | _CellObject | _BoxObject; $$validRootSettingValue = Inherited | _? (AssociationQ@*Association); (* ::**************************************************************************************************************:: *) (* ::Section::Closed:: *) (*Defaults*) -$ChatPost = None; -$ChatPre = None; -$DefaultModel := If[ $VersionNumber >= 13.3, "gpt-4", "gpt-3.5-turbo" ]; +$ChatPost = None; +$ChatPre = None; +$DefaultModel = <| "Service" -> "OpenAI", "Name" -> "gpt-4" |>; (* ::**************************************************************************************************************:: *) (* ::Subsection::Closed:: *) diff --git a/Source/Chatbook/UI.wl b/Source/Chatbook/UI.wl index 8f201353..7fa61a32 100644 --- a/Source/Chatbook/UI.wl +++ b/Source/Chatbook/UI.wl @@ -795,6 +795,10 @@ tr[name_?StringQ] := name (* ::**************************************************************************************************************:: *) (* ::Section::Closed:: *) (*Cell Dingbats*) + +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*MakeChatInputActiveCellDingbat*) MakeChatInputActiveCellDingbat[ ] := DynamicModule[ { cell }, trackedDynamic[ MakeChatInputActiveCellDingbat @ cell, { "ChatBlock" } ], @@ -856,8 +860,9 @@ MakeChatInputActiveCellDingbat[cell_CellObject] := Module[{ button ]; -(*====================================*) - +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*MakeChatInputCellDingbat*) MakeChatInputCellDingbat[] := PaneSelector[ { @@ -875,8 +880,9 @@ MakeChatInputCellDingbat[] := ImageSize -> All ] -(*====================================*) - +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*MakeChatDelimiterCellDingbat*) MakeChatDelimiterCellDingbat[ ] := DynamicModule[ { cell }, trackedDynamic[ MakeChatDelimiterCellDingbat @ cell, { "ChatBlock" } ], @@ -946,8 +952,9 @@ MakeChatDelimiterCellDingbat[cell_CellObject] := Module[{ button ]; -(*====================================*) - +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*makeChatActionMenu*) SetFallthroughError[makeChatActionMenu] makeChatActionMenu[ @@ -1091,6 +1098,7 @@ makeChatActionMenu[ }]]; makeChatActionMenuContent[ + targetObj, containerType, personas, models, @@ -1120,8 +1128,9 @@ makeChatActionMenu[ ] ]] -(*====================================*) - +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*makeChatActionMenuContent*) SetFallthroughError[makeChatActionMenuContent] Options[makeChatActionMenuContent] = { @@ -1134,6 +1143,7 @@ Options[makeChatActionMenuContent] = { } makeChatActionMenuContent[ + targetObj_, containerType : "Input" | "Delimiter" | "Toolbar", personas_?AssociationQ, models_?AssociationQ, @@ -1212,21 +1222,6 @@ makeChatActionMenuContent[ ], personas ], - {"Models"}, - KeyValueMap[ - {model, settings} |-> ( - { - alignedMenuIcon[ - model, - modelValue, - getModelMenuIcon[settings] - ], - modelDisplayName[model], - Hold[callback["Model", model]] - } - ), - models - ], { ConfirmReplace[containerType, { "Input" | "Toolbar" -> Nothing, @@ -1243,17 +1238,18 @@ makeChatActionMenuContent[ {alignedMenuIcon[getIcon["PersonaOther"]], "Add & Manage Personas\[Ellipsis]", "PersonaManage"}, {alignedMenuIcon[getIcon["ToolManagerRepository"]], "Add & Manage Tools\[Ellipsis]", "ToolManage"}, Delimiter, + { + alignedMenuIcon[getIcon["ChatBlockSettingsMenuIcon"]], + submenuLabel[ "Models" ], + Hold @ With[ { root = EvaluationBox[ ] }, + AttachSubmenu[ root, createServiceMenu[ targetObj, ParentCell @ root ] ] + ] + }, { alignedMenuIcon[getIcon["AdvancedSettings"]], - Grid[ - {{ - Item["Advanced Settings", ItemSize -> Fit, Alignment -> Left], - RawBoxes[TemplateBox[{}, "Triangle"]] - }}, - Spacings -> 0 - ], + submenuLabel[ "Advanced Settings" ], Hold @ AttachSubmenu[ - EvaluationCell[], + EvaluationBox[], advancedSettingsMenu ] } @@ -1266,57 +1262,175 @@ makeChatActionMenuContent[ $chatMenuWidth ]; - menu + Cell[ BoxData @ ToBoxes @ menu, "AttachedChatMenu" ] ]] -(*====================================*) +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*getIcon*) +getIcon[ name_ ] := RawBoxes @ TemplateBox[ { }, name ]; -(* getIcon[filename_?StringQ] := Module[{ - icon -}, - icon = Import @ FileNameJoin @ { - PacletObject[ "Wolfram/Chatbook" ][ "AssetLocation", "Icons" ], - filename - }; - - If[!MatchQ[icon, _Graphics], - Raise[ - ChatbookError, - "Unexpected result loading icon from from file ``: ``", - filename, - InputForm[icon] - ]; - ]; +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*submenuLabel*) +submenuLabel // beginDefinition; - (* NOTE: If the graphic doesn't have an existing BaselinePosition set, - use a default baseline that looks vertically centered for most visually - balanced icons. *) - If[BaselinePosition /. Options[icon, BaselinePosition] === Automatic, - (* TODO: Force the image size too. *) - icon = Show[icon, BaselinePosition -> Scaled[0.24]]; - ]; +submenuLabel[ label_ ] := Grid[ + { { Item[ label, ItemSize -> Fit, Alignment -> Left ], RawBoxes @ TemplateBox[ { }, "Triangle" ] } }, + Spacings -> 0 +]; - (* Cache the icon so we don't have to load it from disk again. *) - getIcon[filename] = icon; +submenuLabel // endDefinition; - icon -] *) +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*Model selection submenu*) -getIcon[ name_ ] := RawBoxes @ TemplateBox[ { }, name ]; +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*createServiceMenu*) +createServiceMenu // beginDefinition; + +createServiceMenu[ obj_, root_ ] := + With[ { model = currentChatSettings[ obj, "Model" ] }, + MakeMenu[ + Join[ + { "Services" }, + (createServiceItem[ obj, model, root, #1 ] &) /@ getAvailableServiceNames[ ] + ], + GrayLevel[ 0.85 ], + 120 + ] + ]; +createServiceMenu // endDefinition; +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*createServiceItem*) +createServiceItem // beginDefinition; -(*========================================================*) -(* Chat settings lookup helpers *) -(*========================================================*) +createServiceItem[ obj_, model_, root_, service_String ] := { + serviceSelectionCheckmark[ model, service ], + submenuLabel @ service, + Hold @ AttachSubmenu[ EvaluationBox[ ], dynamicModelMenu[ obj, root, model, service ] ] +}; + +createServiceItem // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*serviceSelectionCheckmark*) +serviceSelectionCheckmark // beginDefinition; +serviceSelectionCheckmark[ KeyValuePattern[ "Service" -> service_String ], service_String ] := $currentSelectionCheck; +serviceSelectionCheckmark[ _String, "OpenAI" ] := $currentSelectionCheck; +serviceSelectionCheckmark[ _, _ ] := Style[ $currentSelectionCheck, ShowContents -> False ]; +serviceSelectionCheckmark // endDefinition; + +$currentSelectionCheck = Style[ "\[Checkmark]", FontColor -> GrayLevel[ 0.25 ] ]; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*dynamicModelMenu*) +dynamicModelMenu // beginDefinition; + +dynamicModelMenu[ obj_, root_, model_, service_? modelListCachedQ ] := + makeServiceModelMenu[ obj, root, model, service ]; + +dynamicModelMenu[ obj_, root_, model_, service_ ] := + DynamicModule[ { display }, + display = MakeMenu[ + { + { service }, + { + None, + Pane[ + Column @ { + Style[ "Getting available models\[Ellipsis]", "ChatMenuLabel" ], + ProgressIndicator[ Appearance -> "Percolate" ] + }, + ImageMargins -> 5 + ], + None + } + }, + GrayLevel[ 0.85 ], + 200 + ]; + + Dynamic[ display, TrackedSymbols :> { display } ], + Initialization :> Quiet[ + Needs[ "Wolfram`Chatbook`" -> None ]; + display = makeServiceModelMenu[ obj, root, model, service ] + ], + SynchronousInitialization -> False + ]; +dynamicModelMenu // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*makeServiceModelMenu*) +makeServiceModelMenu // beginDefinition; + +makeServiceModelMenu[ obj_, root_, model_, service_String ] := + makeServiceModelMenu[ obj, root, model, service, getServiceModelList @ service ]; + +makeServiceModelMenu[ obj_, root_, model_, service_String, models_List ] := + MakeMenu[ + Join[ + { service }, + Map[ + Function @ { + alignedMenuIcon[ modelSelectionCheckmark[ model, #Name ], #Icon ], + #DisplayName, + Hold[ removeChatMenus @ root; setModel[ obj, #1 ] ] + }, + Union @ models + ] + ], + GrayLevel[ 0.85 ], + 280 + ]; + +makeServiceModelMenu // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*modelSelectionCheckmark*) +modelSelectionCheckmark // beginDefinition; +modelSelectionCheckmark[ KeyValuePattern[ "Name" -> model_String ], model_String ] := $currentSelectionCheck; +modelSelectionCheckmark[ model_String, model_String ] := $currentSelectionCheck; +modelSelectionCheckmark[ _, _ ] := Style[ $currentSelectionCheck, ShowContents -> False ]; +modelSelectionCheckmark // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*setModel*) +setModel // beginDefinition; + +setModel[ obj_, KeyValuePattern @ { "Service" -> service_String, "Name" -> model_String } ] := ( + CurrentValue[ obj, { TaggingRules, "ChatNotebookSettings", "Model" } ] = + <| "Service" -> service, "Name" -> model |> +); + +setModel // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*Chat settings lookup helpers*) + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*absoluteCurrentValue*) SetFallthroughError[absoluteCurrentValue] absoluteCurrentValue[cell_, {TaggingRules, "ChatNotebookSettings", key_}] := currentChatSettings[cell, key] absoluteCurrentValue[cell_, keyPath_] := AbsoluteCurrentValue[cell, keyPath] -(*====================================*) - +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*currentValueOrigin*) currentValueOrigin // beginDefinition; (* @@ -1355,8 +1469,9 @@ currentValueOrigin[ currentValueOrigin // endDefinition; -(*====================================*) - +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*getModelsMenuItems*) getModelsMenuItems[] := Module[{ items }, @@ -1378,10 +1493,13 @@ getModelsMenuItems[] := Module[{ ] -(*========================================================*) -(* Menu construction helpers *) -(*========================================================*) +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*Menu construction helpers*) +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*alignedMenuIcon*) SetFallthroughError[alignedMenuIcon] alignedMenuIcon[possible_, current_, icon_] := alignedMenuIcon[styleListItem[possible, current], icon] @@ -1389,8 +1507,9 @@ alignedMenuIcon[check_, icon_] := Row[{check, " ", resizeMenuIcon[icon]}] (* If menu item does not utilize a checkmark, use an invisible one to ensure it is left-aligned with others *) alignedMenuIcon[icon_] := alignedMenuIcon[Style["\[Checkmark]", ShowContents -> False], icon] -(*====================================*) - +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*resizeMenuIcon*) resizeMenuIcon[ icon: _Graphics|_Graphics3D ] := Show[ icon, ImageSize -> { 21, 21 } ]; @@ -1401,8 +1520,9 @@ resizeMenuIcon[ icon_ ] := Pane[ ContentPadding -> False ]; -(*====================================*) - +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*styleListItem*) SetFallthroughError[styleListItem] (* @@ -1430,10 +1550,13 @@ styleListItem[ }] ) -(*========================================================*) -(* Persona property lookup helpers *) -(*========================================================*) +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*Persona property lookup helpers*) +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*personaDisplayName*) SetFallthroughError[personaDisplayName] personaDisplayName[name_String] := personaDisplayName[name, GetCachedPersonaData[name]] @@ -1441,8 +1564,9 @@ personaDisplayName[name_String, data_Association] := personaDisplayName[name, da personaDisplayName[name_String, displayName_String] := displayName personaDisplayName[name_String, _] := name -(*====================================*) - +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*getPersonaMenuIcon*) SetFallthroughError[getPersonaMenuIcon]; getPersonaMenuIcon[ name_String ] := getPersonaMenuIcon @ Lookup[ GetPersonasAssociation[ ], name ]; @@ -1462,14 +1586,18 @@ getPersonaMenuIcon[ expr_, "Full" ] := icon_ :> icon }] - +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*getPersonaIcon*) getPersonaIcon[ expr_ ] := getPersonaMenuIcon[ expr, "Full" ]; +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*Model property lookup helpers*) -(*========================================================*) -(* Model property lookup helpers *) -(*========================================================*) - +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*getModelMenuIcon*) SetFallthroughError[getModelMenuIcon] getModelMenuIcon[settings_?AssociationQ] := Module[{}, @@ -1490,11 +1618,13 @@ getModelMenuIcon[settings_?AssociationQ, "Full"] := icon_ :> icon }] +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*Generic Utilities*) -(*========================================================*) -(* Generic Utilities *) -(*========================================================*) - +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*nestedLookup*) SetFallthroughError[nestedLookup] Attributes[nestedLookup] = {HoldRest} @@ -1517,12 +1647,14 @@ nestedLookup[as_, key:Except[_List], default_] := nestedLookup[as_, keys_] := nestedLookup[as, keys, Missing["KeySequenceAbsent", keys]] +(* ::**************************************************************************************************************:: *) +(* ::Section::Closed:: *) +(*Package Footer*) +If[ Wolfram`ChatbookInternal`$BuildingMX, + Null; +]; -(*========================================================*) - - -End[] - -EndPackage[] +(* :!CodeAnalysis::EndBlock:: *) -(* :!CodeAnalysis::EndBlock:: *) \ No newline at end of file +End[ ]; +EndPackage[ ]; \ No newline at end of file From 9491c1fa2e5357406c025d781a8cf62e881f3fe4 Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Tue, 5 Dec 2023 18:16:22 -0500 Subject: [PATCH 03/50] Fixed notebook toolbar chat menu --- Source/Chatbook/Menus.wl | 57 +++++++++++---- Source/Chatbook/UI.wl | 152 +++++++++++++++++---------------------- 2 files changed, 108 insertions(+), 101 deletions(-) diff --git a/Source/Chatbook/Menus.wl b/Source/Chatbook/Menus.wl index 6eaf81e2..81fd9cc7 100644 --- a/Source/Chatbook/Menus.wl +++ b/Source/Chatbook/Menus.wl @@ -74,6 +74,21 @@ MakeMenu // endDefinition; (*menuItem*) menuItem // beginDefinition; +menuItem[ spec: KeyValuePattern[ "Content" -> content_ ] ] := + menuItem @ <| spec, "Content" :> content |>; + +menuItem[ spec: KeyValuePattern @ { "Type" -> "Submenu", "Content" :> content_ } ] := + EventHandler[ + menuItem[ + Lookup[ spec, "Icon", Spacer[ 0 ] ], + submenuLabel @ Lookup[ spec, "Label", "" ], + None + ], + { + "MouseEntered" :> With[ { root = EvaluationBox[ ] }, AttachSubmenu[ root, content ] ] + } + ]; + menuItem[ { args__ } ] := menuItem @ args; @@ -111,33 +126,46 @@ menuItem[ None, content_, None ] := content; menuItem[ icon_, label_, None ] := - menuItem[ - icon, - label, - Hold[ - MessageDialog[ "Not Implemented" ]; - NotebookDelete @ EvaluationCell[ ]; - ] - ]; + menuItem[ icon, label, Hold @ Null ]; menuItem[ icon_, label_, code_ ] := RawBoxes @ TemplateBox[ { ToBoxes @ icon, ToBoxes @ label, code }, "ChatMenuItem" ]; menuItem // endDefinition; +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*submenuLabel*) +submenuLabel // beginDefinition; + +submenuLabel[ label_ ] := Grid[ + { { Item[ label, ItemSize -> Fit, Alignment -> Left ], RawBoxes @ TemplateBox[ { }, "Triangle" ] } }, + Spacings -> 0 +]; + +submenuLabel // endDefinition; + (* ::**************************************************************************************************************:: *) (* ::Section::Closed:: *) (*AttachSubmenu*) AttachSubmenu[ parentMenu_, submenu: Cell[ __, "AttachedChatMenu", ___ ] ] := Enclose[ - Module[ { pos, oPos, offset }, + Module[ { pos, oPos, offsetX, offsetY, magnification }, + NotebookDelete @ Cells[ parentMenu, AttachedCell -> True, CellStyle -> "AttachedChatMenu" ]; { pos, oPos } = ConfirmMatch[ determineAttachmentPosition[ ], { { _, _ }, { _, _ } }, "Position" ]; - offset = If[ MatchQ[ pos, { Left, _ } ], { -3, 0 }, { 3, 0 } ]; + offsetX = If[ MatchQ[ pos, { Left, _ } ], -3, 3 ]; + offsetY = If[ MatchQ[ pos, { _, Top } ], 5, -5 ]; + + magnification = Replace[ + AbsoluteCurrentValue[ parentMenu, Magnification ], + Except[ _? NumberQ ] :> If[ $OperatingSystem === "Windows", 0.75, 1 ] + ]; + AttachCell[ parentMenu, - submenu, + Append[ submenu, Magnification -> magnification ], pos, - Offset[ offset, { 0, 0 } ], + Offset[ { offsetX, offsetY }, { 0, 0 } ], oPos, RemovalConditions -> { "MouseClickOutside", "EvaluatorQuit" } ] @@ -160,11 +188,12 @@ AttachSubmenu[ expr_ ] := determineAttachmentPosition // beginDefinition; determineAttachmentPosition[ ] := determineAttachmentPosition @ MousePosition[ "WindowScaled" ]; determineAttachmentPosition[ pos_List ] := determineAttachmentPosition[ pos, quadrant @ pos ]; -determineAttachmentPosition[ _, { h_, v_ } ] := { { Replace[ h, { Left -> Right, Right -> Left } ], v }, { h, v } }; +determineAttachmentPosition[ _, { h_, v_ } ] := { { Replace[ h, { Left -> Right, Right -> Left } ], v }, { h, Center } }; determineAttachmentPosition // endDefinition; quadrant // beginDefinition; -quadrant[ { x_? NumberQ, y_? NumberQ } ] := quadrant[ TrueQ[ x >= 0.5 ], TrueQ[ y >= 0.5 ] ]; +quadrant[ None ] := None; +quadrant[ { x_? NumberQ, y_? NumberQ } ] := quadrant[ TrueQ[ x >= 0.67 ], TrueQ[ y >= 0.67 ] ]; quadrant[ True , True ] := { Right, Bottom }; quadrant[ True , False ] := { Right, Top }; quadrant[ False, True ] := { Left , Bottom }; diff --git a/Source/Chatbook/UI.wl b/Source/Chatbook/UI.wl index 7fa61a32..1460c348 100644 --- a/Source/Chatbook/UI.wl +++ b/Source/Chatbook/UI.wl @@ -262,26 +262,7 @@ CreateToolbarContent[] := With[{ PaneSelector[ { True :> ( - Dynamic @ Refresh[ - Column[{ - Pane[ - makeEnableAIChatFeaturesLabel[True], - ImageMargins -> {{5, 20}, {2.5, 2.5}} - ], - - Pane[ - makeAutomaticResultAnalysisCheckbox[EvaluationNotebook[]], - ImageMargins -> {{5, 20}, {2.5, 2.5}} - ], - - makeChatActionMenu[ - "Toolbar", - EvaluationNotebook[], - Automatic - ] - }], - None - ] + Dynamic[ makeToolbarMenuContent @ menuCell, SingleEvaluation -> True, DestroyAfterEvaluation -> True ] ), False :> ( Dynamic @ Refresh[ @@ -293,7 +274,29 @@ CreateToolbarContent[] := With[{ Dynamic @ CurrentValue[menuCell, {TaggingRules, "IsChatEnabled"}], ImageSize -> Automatic ] -] +]; + +makeToolbarMenuContent[ menuCell_ ] := Enclose[ + Module[ { items, item1, item2, new }, + + items = ConfirmBy[ makeChatActionMenu[ "Toolbar", EvaluationNotebook[ ], Automatic, "List" ], ListQ, "Items" ]; + + item1 = Pane[ + makeEnableAIChatFeaturesLabel @ True, + ImageMargins -> { { 5, 20 }, { 2.5, 2.5 } } + ]; + + item2 = Pane[ + makeAutomaticResultAnalysisCheckbox @ EvaluationNotebook[ ], + ImageMargins -> { { 5, 20 }, { 2.5, 2.5 } } + ]; + + new = Join[ { { None, item1, None }, { None, item2, None } }, items ]; + + MakeMenu[ new, Transparent, $chatMenuWidth ] + ], + throwInternalFailure +]; (*====================================*) @@ -346,11 +349,7 @@ tryMakeChatEnabledNotebook[ "", RawBoxes @ Cell["Are you sure you wish to continue?", "Text"] }], - Background -> White, - WindowMargins -> ConfirmReplace[ - MousePosition["ScreenAbsolute"], - {x_, y_} :> {{x, Automatic}, {Automatic, y}} - ] + Background -> White ], _?BooleanQ ] @@ -962,7 +961,8 @@ makeChatActionMenu[ targetObj : _CellObject | _NotebookObject, (* The cell that will be the parent of the attached cell that contains this chat action menu content. *) - attachedCellParent : _CellObject | Automatic + attachedCellParent : _CellObject | Automatic, + format_ : "Cell" ] := With[{ closeMenu = ConfirmReplace[attachedCellParent, { parent_CellObject -> Function[ @@ -981,7 +981,6 @@ makeChatActionMenu[ }] }, Module[{ personas = GetPersonasAssociation[], - models, actionCallback }, (*--------------------------------*) @@ -1048,14 +1047,6 @@ makeChatActionMenu[ ]; ]; - (*--------------------------------*) - (* Process models list *) - (*--------------------------------*) - - models = getModelsMenuItems[]; - - RaiseConfirmMatch[models, <| (_?StringQ -> _?AssociationQ)... |>]; - (*--------------------------------*) actionCallback = Function[{field, value}, Replace[field, { @@ -1074,13 +1065,6 @@ makeChatActionMenu[ SetOptions[targetObj, CellDingbat -> Inherited]; ]; ), - "Model" :> ( - CurrentValue[ - targetObj, - {TaggingRules, "ChatNotebookSettings", "Model"} - ] = value; - closeMenu[]; - ), "Role" :> ( CurrentValue[ targetObj, @@ -1101,7 +1085,7 @@ makeChatActionMenu[ targetObj, containerType, personas, - models, + format, "ActionCallback" -> actionCallback, "PersonaValue" -> currentValueOrigin[ targetObj, @@ -1146,7 +1130,7 @@ makeChatActionMenuContent[ targetObj_, containerType : "Input" | "Delimiter" | "Toolbar", personas_?AssociationQ, - models_?AssociationQ, + format_, OptionsPattern[] ] := With[{ callback = OptionValue["ActionCallback"] @@ -1238,50 +1222,43 @@ makeChatActionMenuContent[ {alignedMenuIcon[getIcon["PersonaOther"]], "Add & Manage Personas\[Ellipsis]", "PersonaManage"}, {alignedMenuIcon[getIcon["ToolManagerRepository"]], "Add & Manage Tools\[Ellipsis]", "ToolManage"}, Delimiter, - { - alignedMenuIcon[getIcon["ChatBlockSettingsMenuIcon"]], - submenuLabel[ "Models" ], - Hold @ With[ { root = EvaluationBox[ ] }, - AttachSubmenu[ root, createServiceMenu[ targetObj, ParentCell @ root ] ] - ] - }, - { - alignedMenuIcon[getIcon["AdvancedSettings"]], - submenuLabel[ "Advanced Settings" ], - Hold @ AttachSubmenu[ - EvaluationBox[], - advancedSettingsMenu - ] - } - } - ]; - - menu = MakeMenu[ - menuItems, - GrayLevel[0.85], - $chatMenuWidth - ]; + <| + "Label" -> "Models", + "Type" -> "Submenu", + "Icon" -> alignedMenuIcon @ getIcon[ "ChatBlockSettingsMenuIcon" ], + "Content" :> createServiceMenu[ targetObj, ParentCell @ EvaluationCell[ ] ] + |>, + <| + "Label" -> "Advanced Settings", + "Type" -> "Submenu", + "Icon" -> alignedMenuIcon @ getIcon[ "AdvancedSettings" ], + "Content" -> advancedSettingsMenu + |> + } + ]; - Cell[ BoxData @ ToBoxes @ menu, "AttachedChatMenu" ] -]] + Replace[ + format, + { + "List" :> menuItems + , + "Expression" :> MakeMenu[ menuItems, GrayLevel[ 0.85 ], $chatMenuWidth ] + , + "Cell"|Automatic :> Cell[ + BoxData @ ToBoxes @ MakeMenu[ menuItems, GrayLevel[ 0.85 ], $chatMenuWidth ], + "AttachedChatMenu" + ] + , + expr_ :> throwInternalFailure[ makeChatActionMenuContent, expr ] + } + ] +]]; (* ::**************************************************************************************************************:: *) (* ::Subsubsection::Closed:: *) (*getIcon*) getIcon[ name_ ] := RawBoxes @ TemplateBox[ { }, name ]; -(* ::**************************************************************************************************************:: *) -(* ::Subsubsection::Closed:: *) -(*submenuLabel*) -submenuLabel // beginDefinition; - -submenuLabel[ label_ ] := Grid[ - { { Item[ label, ItemSize -> Fit, Alignment -> Left ], RawBoxes @ TemplateBox[ { }, "Triangle" ] } }, - Spacings -> 0 -]; - -submenuLabel // endDefinition; - (* ::**************************************************************************************************************:: *) (* ::Subsection::Closed:: *) (*Model selection submenu*) @@ -1310,11 +1287,12 @@ createServiceMenu // endDefinition; (*createServiceItem*) createServiceItem // beginDefinition; -createServiceItem[ obj_, model_, root_, service_String ] := { - serviceSelectionCheckmark[ model, service ], - submenuLabel @ service, - Hold @ AttachSubmenu[ EvaluationBox[ ], dynamicModelMenu[ obj, root, model, service ] ] -}; +createServiceItem[ obj_, model_, root_, service_String ] := <| + "Type" -> "Submenu", + "Label" -> service, + "Icon" -> serviceSelectionCheckmark[ model, service ], + "Content" :> dynamicModelMenu[ obj, root, model, service ] +|>; createServiceItem // endDefinition; From 0876d50ef8604ed6e9f524ab446c62a5ea819001 Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Wed, 6 Dec 2023 07:28:54 -0500 Subject: [PATCH 04/50] Sort models by type --- Source/Chatbook/Models.wl | 16 +++++++++++----- Source/Chatbook/Services.wl | 34 ++++++++++++++++++++++------------ 2 files changed, 33 insertions(+), 17 deletions(-) diff --git a/Source/Chatbook/Models.wl b/Source/Chatbook/Models.wl index 68059153..0a9b8b93 100644 --- a/Source/Chatbook/Models.wl +++ b/Source/Chatbook/Models.wl @@ -142,6 +142,9 @@ toModelName // beginDefinition; toModelName[ KeyValuePattern @ { "Service" -> service_, "Name"|"Model" -> model_ } ] := toModelName @ { service, model }; +toModelName[ KeyValuePattern[ "Name"|"Model" -> model_ ] ] := + toModelName @ model; + toModelName[ { service_String, name_String } ] := toModelName @ name; toModelName[ name_String? StringQ ] := toModelName[ name ] = @@ -284,20 +287,23 @@ standardizeModelData[ list_List ] := standardizeModelData[ name_String ] := standardizeModelData[ name ] = standardizeModelData @ <| "Name" -> name |>; -standardizeModelData[ model: KeyValuePattern @ { "Name" -> _String, "DisplayName" -> _String, "Icon" -> _ } ] := - Association @ model; - -standardizeModelData[ model_Association? AssociationQ ] := +standardizeModelData[ model: KeyValuePattern @ { } ] := standardizeModelData[ model ] = <| - "Name" -> modelName @ model, "DisplayName" -> modelDisplayName @ model, + "FineTuned" -> fineTunedModelQ @ model, "Icon" -> modelIcon @ model, + "Multimodal" -> multimodalModelQ @ model, + "Name" -> modelName @ model, + "Snapshot" -> snapshotModelQ @ model, model |>; standardizeModelData[ service_String, models_List ] := standardizeModelData[ service, # ] & /@ models; +standardizeModelData[ service_String, model_String ] := + standardizeModelData @ <| "Service" -> service, "Name" -> model |>; + standardizeModelData[ service_String, model_ ] := With[ { as = standardizeModelData @ model }, (standardizeModelData[ service, model ] = <| "Service" -> service, as |>) /; AssociationQ @ as diff --git a/Source/Chatbook/Services.wl b/Source/Chatbook/Services.wl index eaadba2e..675ae8fd 100644 --- a/Source/Chatbook/Services.wl +++ b/Source/Chatbook/Services.wl @@ -26,7 +26,9 @@ $ContextAliases[ "llm`" ] = "LLMServices`"; (* ::Section::Closed:: *) (*Configuration*) $enableLLMServices = Automatic; -$servicesLoaded := False; +$modelListCache = <| |>; +$modelSortOrder = { "Snapshot", "FineTuned", "DisplayName" }; +$servicesLoaded = False; $useLLMServices := MatchQ[ $enableLLMServices, Automatic|True ] && TrueQ @ $llmServicesAvailable; $llmServicesAvailable := $llmServicesAvailable = ( @@ -42,7 +44,7 @@ $llmServicesAvailable := $llmServicesAvailable = ( (* ::Subsection::Closed:: *) (*modelListCachedQ*) modelListCachedQ // beginDefinition; -modelListCachedQ[ name_String ] := False; +modelListCachedQ[ service_String ] := ListQ @ Lookup[ $modelListCache, service ]; modelListCachedQ // endDefinition; (* ::**************************************************************************************************************:: *) @@ -78,13 +80,17 @@ getAvailableServiceNames0 // endDefinition; (*getServiceModels*) getServiceModelList // beginDefinition; -getServiceModelList[ name_String ] := - getServiceModelList[ name, llm`LLMServiceInformation[ llm`ChatSubmit, name ] ]; +getServiceModelList[ service_String ] := + Lookup[ + $modelListCache, + service, + getServiceModelList[ service, llm`LLMServiceInformation[ llm`ChatSubmit, service ] ] + ]; -getServiceModelList[ name_String, info_Association ] := - getServiceModelList[ name, info, getModelListQuietly @ info ]; +getServiceModelList[ service_String, info_Association ] := + getServiceModelList[ service, info, getModelListQuietly @ info ]; -getServiceModelList[ name_, info_, Missing[ "NotConnected" ] ] := +getServiceModelList[ service_, info_, Missing[ "NotConnected" ] ] := Missing[ "NotConnected" ]; getServiceModelList[ "OpenAI", info_, models: { "gpt-4", "gpt-3.5-turbo-0613" } ] := @@ -92,11 +98,15 @@ getServiceModelList[ "OpenAI", info_, models: { "gpt-4", "gpt-3.5-turbo-0613" } getServiceModelList[ "OpenAI", info, full ] /; MatchQ[ full, Except[ models, { __String } ] ] ]; -getServiceModelList[ name_String, info_, models: { ___String } ] := - WithCleanup[ - getServiceModelList[ name ] = standardizeModelData[ name, <| "Service" -> name, "Name" -> #1 |> & /@ models ], - modelListCachedQ[ name ] = True - ]; +getServiceModelList[ service_String, info_, models0_List ] := Enclose[ + Module[ { models, ordering, sorted }, + models = ConfirmMatch[ standardizeModelData[ service, models0 ], { ___Association }, "Models" ]; + ordering = Lookup /@ ConfirmMatch[ $modelSortOrder, { __String }, "ModelSortOrder" ]; + sorted = SortBy[ models, ordering ]; + $modelListCache[ service ] = sorted + ], + throwInternalFailure +]; getServiceModelList // endDefinition; From 4a4a979e8917db97b5f51ce640913978df04df7e Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Wed, 6 Dec 2023 07:29:20 -0500 Subject: [PATCH 05/50] Reduce width of root chat menu --- Source/Chatbook/Menus.wl | 2 +- Source/Chatbook/UI.wl | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/Source/Chatbook/Menus.wl b/Source/Chatbook/Menus.wl index 81fd9cc7..dd5156e2 100644 --- a/Source/Chatbook/Menus.wl +++ b/Source/Chatbook/Menus.wl @@ -193,7 +193,7 @@ determineAttachmentPosition // endDefinition; quadrant // beginDefinition; quadrant[ None ] := None; -quadrant[ { x_? NumberQ, y_? NumberQ } ] := quadrant[ TrueQ[ x >= 0.67 ], TrueQ[ y >= 0.67 ] ]; +quadrant[ { x_? NumberQ, y_? NumberQ } ] := quadrant[ TrueQ[ x >= 0.5 ], TrueQ[ y >= 0.67 ] ]; quadrant[ True , True ] := { Right, Bottom }; quadrant[ True , False ] := { Right, Top }; quadrant[ False, True ] := { Left , Bottom }; diff --git a/Source/Chatbook/UI.wl b/Source/Chatbook/UI.wl index 1460c348..552c131d 100644 --- a/Source/Chatbook/UI.wl +++ b/Source/Chatbook/UI.wl @@ -49,7 +49,7 @@ Needs[ "Wolfram`Chatbook`Utils`" ]; (* ::**************************************************************************************************************:: *) (* ::Section::Closed:: *) (*Configuration*) -$chatMenuWidth = 260; +$chatMenuWidth = 220; (* ::**************************************************************************************************************:: *) (* ::Section::Closed:: *) From bed75afac297e5a22eb7ad548d4cadf4a6a325c0 Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Wed, 6 Dec 2023 13:16:38 -0500 Subject: [PATCH 06/50] Added service icons and rebuilt stylesheet --- Assets/DisplayFunctions.wxf | Bin 502259 -> 513906 bytes Assets/Icons.wxf | Bin 5524 -> 5748 bytes .../Resources/Icons/ServiceIconAnthropic.wl | 42 ++ .../Resources/Icons/ServiceIconOpenAI.wl | 311 +++++++++++++ Developer/Resources/Icons/ServiceIconPaLM.wl | 118 +++++ FrontEnd/StyleSheets/Chatbook.nb | 425 +++++++++++++++++- 6 files changed, 888 insertions(+), 8 deletions(-) create mode 100644 Developer/Resources/Icons/ServiceIconAnthropic.wl create mode 100644 Developer/Resources/Icons/ServiceIconOpenAI.wl create mode 100644 Developer/Resources/Icons/ServiceIconPaLM.wl diff --git a/Assets/DisplayFunctions.wxf b/Assets/DisplayFunctions.wxf index 14ed96bbfcf2ab9f761844105fe032ed7b70af7e..674588ee5958b206a9c36fdc7d45618642fa079f 100644 GIT binary patch delta 8202 zcmaJ`2Ur!y7UmW@DAJ@zxrh`Iv5SpeEGUXCc8mxj28f~#VAq8h#oka?(b#MB5!6^P ziY3uRjK)H2BsSDU5gQ7kfbY!gy|W{G-@D)E2iKpOojK<}=lthv`E}1XxnAa>9mB^3 z4|2=Cs&UKI&C{vo>D2Rdn!`Hnx^gGSK?!I|QhY*W{KS;-l(a-NaZ*xz_SVEkqIap8 zmB@dswibf}O)bU7yET5IdxP|=fJI-4$0!=O0>=sg^GqN2lG0Pm{X9U^bD0*xsFApQfR$fTU zTv_}n+RSpqJ{KPKdN9K=*W6D&VHc~L+b7k)mhIh6kMve~%1F+7_>6Ecf;=C1%yS;I zn;4#}@^MW)-psF^*C`IsUvh7ap3>j5KwP<1ohu}+EStp*@iB6Ca$l#WJc<`?cbU$b zT(U%SBM9-^TCkDAfy(EouqDJ^xhnVnb4J}0byu;!n`xZb@2tkhz5&C!{*w|?!XpXg zPOUY!7EkWiTFI0=<|ErVjc;M9YO`UDLdDQMwr+!zj zHkJ|Rj~8EDh;M9U4MnC*cDKDB+(=$Sck|7!&U!o2MUM!nX^0*{v4|q{aBd7cATW^5 z>+SfVC!KlJ;wS(5)`vah2Rgh7|6|;m20Z%0f6KzWIBz3J6SK_7HQg5b8-dpRA7 zU4V?>-Tw5q=Mf>^$v_!7@Zjm1gHaA*T(r4^uqY3{AqY?i#@E-DG69ND@gNXR8gZn& zrYN+Tyusbc!b&6HpYNp zbABH?_zVA7Pa}(bYAVw2cLtAc>j7tQG%SKOv*KC}Y0(>k`p4g<6l~66j?ibs{LmXs zfc``41t0wGC37KTh(OX6!fVdi!Xk)KuotuFjypW+9Xv>ZJOnG+9B9ZRbx@Y`?S72u zO(te)&-Djn?&-p`14y{+l_?S{=Z8yl7 zKN&-I;8Sl`BH}E47#j=4P_%qU`x1zXstOMQ)8@?QU?V#+lIg84Dg9@|j?0Wz6z z+ZbYkKfEy{69QOp^%Me9KB@GPVkvmD_%ywSj zp<|wb`s96s$pJ5L5PksUs!ws%oTdzNaVx~yNhlJ8*2yfd@!bo&z~lZcE#SJ0U-z8v z(|%zlAh$1r?-LmNkUz}<1l(&smv185M^7^zoq-@Z(%M%H>7a2L4%blRzmzr^NBJ=j zgP2Z^xeN#2^@hl;02{+4l25c@o;v~OGkdtkGlROoD`|Cd70-ni)AxDz1E|0I^);760N6Q_08J0Y5B)c{K6WybFWRFx8}F=Z0Ur zUkR}2R%U9%>M3sW5yo}`?%xFD^FjmkCh21eAow}aT^YGUkNrFZ%E)3zc{l2#HVxW! zK6%YvMnLS?0{Out(>88voIk69sB5QoFwdEazu8G&o@wziFX_vZ+$N9aZj!zTzXo<( zb@7vzydC8h5fd&MZ*_&)=ykuF@(3p{o30FFiAm2|@ko(WDFW4&7Fz+UTFDQ1(bbh-)^?l0 zoS!aI+>9a$JIx1*?D4hck;1m$07WY11EO~UKTa?R>RzX2dxZW2(7(6$fB13&;}G5< z?&s_KY=H5S6J=LDKi#2m?@k~+$rE=lJff8xljV!G4)PkOCB2_%e>CS2ktw?bhOiP( z)jU$jpOo#Y6Q=gyBJ0DurvJK^iHxfHPmlhf`M{wwaFm%pGnRW9+M_3`s^CzyOX^Mg zR!nTpzH(^9yZlNH9d7?#I6L+kBj}V|X!sdj($KmnxIr>_e#Xvb-5QnFmv82cW2pd+ zKjh4w9sPJFLMV?efB(myL!UEI4G%dsb2}2==Zv(x$XINpYUk+&GMHS-T*;(g6KabgZqs_}uQyJ0VM4e*G zqei6<+qs=KlM#^oE4ECt;L+eTU-8olD;cT79{~vDSchVzsfV3D?t`+lXxXDTUf14n zv?8~_J*_Y3Rt0k5F}LGhEreoa`u&X!c2+TKqIOwDJa*T2f#D|dQCa{Z7>7vD-~_6= z^)CmSr)*~yQN67|s5F95b>z<1lOIIo)ZBrQ-(~nQG4o1*mc0E!P)!19y%~tAGnOtS zTY|RnDb9yAxWH6rF@&XvzWB&TpvbH@c>}(7YhXZt{}jUZh-ku;YSOy&1!<(nd=#m( z9aIzYfi+Sp0g4$iEPW2^Jc<8Gk4M(w1lA`#b)W!}NPscfYyc5JfGE1tuK0-?03n6* zE+cQ~n&$$Z1e7xBiRiXuSVUy_dq(+C5kh3MDbszVLl-A5V#6{ zqC`eQ5@D6r6b37b29Z{CMT3YPUo{7eOZt)$raL1l`5v?eijI!bQqfedNmvjsjG6^1 z56i3HrZ8<_ha2Z6wAljco3K#VT=pV$74B>THZq9ajCT9NjzVxs6O9mg&4PK+*H1L| z;t}prf_gH@3!xNhs1?Mm0)o^VwW|9rgt`;8rk)W;(8`Y+-rZ)5_efcHhWw@&0^Gssp@)`7gk#;924KRu z+JiHZ2`_b5c@j$`{?jV1pq53K4MR5Xd&?m_E0`9@2(5YrE!H=6dBq`^sNL(|mmw-? zx+gs3l)OI$WoFxt#T+8(G7Jho)j!F1CqrD`=a2`+HZxfuviT=nO+^W(lvB-$a-MkX ze!-zZYjw-gUo*0tN(_Z6rx%jcj=)qjNl}z@N?A@95&0j$2ndsvb0BfPtEG_wD4Galjp@AI2VUei4Zx{^rH zhp*q_uBlcoJ(P6Vfa&+&%Lttg2_$NURmu>p(cjwk|6z5)2N}V>Yaa>`u>q|9Z?Cs9 z0&|`%3tvISCoSHCG8uX048*?$g{&Wu)=y*v=lb-s0*r^G?Ebe5ZSD-7oez;r%+c_s zjEuLe+VWL4lx79u;y1{2dn?E#3WQD|@bqSR%My7v=u`zrBG8uO#j85LmLZzy6s99- zEEPH$g(JvptPGIiMKuYPj~LxUyYlOIu_UsPohNQ+VQwiXR7ykAZ$sWzlVWZwFQ84T zLjTgDqHhD`HF#!MRt+@;cM?Gfj8ubk2s18U7!Z?ohHXWwVQkpfCxk~eS#OJPX1amf={Z7LMie`s2_00j<6cc#SE{loiy2X@?zr~r=YB#YqL*p-cUsvlyyK=3i zINHs0AekrI)o13(1LC6kl4){mnVFM3NEQd2P+5qZ%hh(`06WtNk#D7P6k`u+EyQDC zDm(KvMV5&^QQo312fAap_2o(jU-CsDNwf=;H8MJKWGGKE{1Rwv$pmH%qdjp(K5q>L zPionzph-ix?WunOm?(|Q7VlVnqaf%7voL9Vl`GG5!b6>=zQd|0ln(_;=5x9+1ZDk{P+Glq(MS98zo zNip?A{-idP@zjc?YCC}pjt&`wQw-A!Qv}bc#%^HRO`@?j!5X5vW-@G>NxTY(;l&13 zgrjP^eJJY#dFFEj`-4JcBIe6jP%7;}76l>=%K#yIJCA9{u^Mps7V->{R_7VhQX1j6 zNL>mEjr6lg3X$`#X1GU2wwRR)gv`c6KnW5VHkgs~)N*97eup_6MTiN(+G5vSmCp53 zSjpMU6<0XqK6cg0LwQh{3)>g}wQkc3$$=!yVxMaoiLukwVPamG%0+O(wHwo}C!Ue+ zVT|?!x}$=AfRMr7P^MC27nGU+0u==cJu_OM2AQD@b=9)8KOmjWbMXnDoi)XKz9t$_Ikf9#>qbpUVx6D zhI2IYAc`n%L=il7ww&%R=WhBS7&^~c(t#N^(8Ces1o7%hiA`^$cZBqQv7_18AEpW~ zIYcIt;y)Z}cKltAr{ik9N44f8aYjiwlSCp-OC&5c5%x%M^$-vW51L)X)M( zGD@$8A!m}zIFd0m8Q$*(Mw5ax!k~1!fJbR^e(DDiw~^^N^f{bIq{T2{bhvcv>;r=w z1$~Ax@<*R%wcCbg!Xs%WRJffcRt1S@GA6gKHFR{rupQ0d3RBfJujD6CT?^tzm2rr? iqqzbhIC|!|$c&sq@$+}AS^4E!_-A@Fzuc_jk^ce``(Mcb delta 48 zcmeygPX6;{Id%&x$7J1LsmT|ar5Y7m6&YIIU;8sSHT;@dc_AKo{G*i~klY0KjiF5&!@I delta 18 acmeyOGew)l!phNiBg+o{&2t29umS)-4+fk7 diff --git a/Developer/Resources/Icons/ServiceIconAnthropic.wl b/Developer/Resources/Icons/ServiceIconAnthropic.wl new file mode 100644 index 00000000..dec08cd1 --- /dev/null +++ b/Developer/Resources/Icons/ServiceIconAnthropic.wl @@ -0,0 +1,42 @@ +Graphics[ + { + Thickness[ 0.0625 ], + Style[ + { + FilledCurve[ + { + { { 0, 2, 0 }, { 0, 1, 0 }, { 0, 1, 0 }, { 0, 1, 0 }, { 0, 1, 0 }, { 0, 1, 0 }, { 0, 1, 0 }, { 0, 1, 0 } }, + { { 0, 2, 0 }, { 0, 1, 0 }, { 0, 1, 0 } } + }, + { + { + { 5.0525, 13.543 }, + { 1.1665, 3.5431 }, + { 3.3395, 3.5431 }, + { 4.1345, 5.6431 }, + { 8.1995, 5.6431 }, + { 8.9945, 3.5431 }, + { 11.167, 3.5431 }, + { 7.2805, 13.543 }, + { 5.0525, 13.543 } + }, + { { 6.1675, 11.015 }, { 7.4975, 7.5011 }, { 4.8375, 7.5011 }, { 6.1675, 11.015 } } + } + ] + }, + FaceForm @ RGBColor[ 0.12157, 0.12157, 0.11765, 1.0 ] + ], + Style[ + { + FilledCurve[ + { { { 0, 2, 0 }, { 0, 1, 0 }, { 0, 1, 0 }, { 0, 1, 0 } } }, + { { { 9.1665, 13.543 }, { 13.042, 3.5432 }, { 15.167, 3.5432 }, { 11.293, 13.543 }, { 9.1665, 13.543 } } } + ] + }, + FaceForm @ RGBColor[ 0.12157, 0.12157, 0.11765, 1.0 ] + ] + }, + ImageSize -> { 17.0, 17.0 }, + PlotRange -> { { -0.5, 16.5 }, { -0.5, 16.5 } }, + AspectRatio -> Automatic +] \ No newline at end of file diff --git a/Developer/Resources/Icons/ServiceIconOpenAI.wl b/Developer/Resources/Icons/ServiceIconOpenAI.wl new file mode 100644 index 00000000..107ffc3c --- /dev/null +++ b/Developer/Resources/Icons/ServiceIconOpenAI.wl @@ -0,0 +1,311 @@ +Graphics[ + { + Thickness[ 0.0625 ], + Style[ + { + FilledCurve[ + { + { { 0, 2, 0 }, { 0, 1, 0 }, { 0, 1, 0 }, { 0, 1, 0 }, { 0, 1, 0 }, { 0, 1, 0 } }, + { + { 0, 2, 0 }, + { 0, 1, 0 }, + { 1, 3, 3 }, + { 1, 3, 3 }, + { 1, 3, 3 }, + { 1, 3, 3 }, + { 1, 3, 3 }, + { 0, 1, 0 }, + { 1, 3, 3 }, + { 1, 3, 3 }, + { 0, 1, 0 } + }, + { + { 1, 4, 3 }, + { 0, 1, 0 }, + { 1, 3, 3 }, + { 1, 3, 3 }, + { 0, 1, 0 }, + { 0, 1, 0 }, + { 0, 1, 0 }, + { 1, 3, 3 }, + { 1, 3, 3 }, + { 1, 3, 3 }, + { 1, 3, 3 } + }, + { { 0, 2, 0 }, { 0, 1, 0 }, { 0, 1, 0 }, { 1, 3, 3 }, { 1, 3, 3 }, { 1, 3, 3 }, { 1, 3, 3 }, { 0, 1, 0 }, { 1, 3, 3 }, { 1, 3, 3 } }, + { { 1, 4, 3 }, { 0, 1, 0 }, { 0, 1, 0 }, { 1, 3, 3 }, { 1, 3, 3 }, { 0, 1, 0 }, { 0, 1, 0 }, { 0, 1, 0 }, { 1, 3, 3 }, { 1, 3, 3 } }, + { { 1, 4, 3 }, { 1, 3, 3 }, { 0, 1, 0 }, { 1, 3, 3 }, { 1, 3, 3 }, { 0, 1, 0 }, { 0, 1, 0 }, { 0, 1, 0 }, { 1, 3, 3 }, { 1, 3, 3 } }, + { { 1, 4, 3 }, { 1, 3, 3 }, { 0, 1, 0 }, { 1, 3, 3 }, { 1, 3, 3 }, { 0, 1, 0 }, { 0, 1, 0 }, { 0, 1, 0 }, { 1, 3, 3 } }, + { + { 1, 4, 3 }, + { 1, 3, 3 }, + { 1, 3, 3 }, + { 1, 3, 3 }, + { 1, 3, 3 }, + { 1, 3, 3 }, + { 1, 3, 3 }, + { 1, 3, 3 }, + { 1, 3, 3 }, + { 1, 3, 3 }, + { 1, 3, 3 }, + { 1, 3, 3 }, + { 1, 3, 3 }, + { 1, 3, 3 }, + { 1, 3, 3 }, + { 1, 3, 3 }, + { 1, 3, 3 }, + { 1, 3, 3 }, + { 1, 3, 3 }, + { 1, 3, 3 }, + { 1, 3, 3 }, + { 1, 3, 3 }, + { 1, 3, 3 }, + { 1, 3, 3 } + } + }, + { + { + { 6.3529, 8.9548 }, + { 8.0239, 9.9098 }, + { 9.6949, 8.9548 }, + { 9.6949, 7.0448 }, + { 8.0239, 6.0898 }, + { 6.3529, 7.0448 }, + { 6.3529, 8.9548 } + }, + { + { 5.6849, 7.4268 }, + { 4.3959, 8.1908 }, + { 4.3959, 11.772 }, + { 4.3959, 12.297 }, + { 4.5389, 12.87 }, + { 4.8249, 13.3 }, + { 5.1119, 13.777 }, + { 5.5409, 14.111 }, + { 6.0189, 14.35 }, + { 6.4959, 14.589 }, + { 7.0689, 14.684 }, + { 7.5939, 14.589 }, + { 8.1189, 14.541 }, + { 8.6449, 14.302 }, + { 9.0739, 13.968 }, + { 9.0739, 13.968 }, + { 9.0269, 13.92 }, + { 8.9789, 13.92 }, + { 5.9229, 12.154 }, + { 5.8279, 12.106 }, + { 5.7799, 12.058 }, + { 5.7319, 11.963 }, + { 5.6849, 11.867 }, + { 5.6849, 11.82 }, + { 5.6849, 11.724 }, + { 5.6849, 7.4268 } + }, + { + { 13.705, 10.101 }, + { 13.705, 10.101 }, + { 13.658, 10.149 }, + { 13.61, 10.149 }, + { 10.554, 11.915 }, + { 10.459, 11.963 }, + { 10.411, 11.963 }, + { 10.316, 11.963 }, + { 10.22, 11.963 }, + { 10.125, 11.963 }, + { 10.077, 11.915 }, + { 6.3529, 9.7668 }, + { 6.3529, 11.247 }, + { 9.4559, 13.061 }, + { 9.9339, 13.347 }, + { 10.459, 13.443 }, + { 11.032, 13.443 }, + { 11.557, 13.443 }, + { 12.082, 13.252 }, + { 12.56, 12.918 }, + { 12.989, 12.583 }, + { 13.371, 12.154 }, + { 13.562, 11.676 }, + { 13.753, 11.199 }, + { 13.801, 10.626 }, + { 13.705, 10.101 } + }, + { + { 12.416, 8.1908 }, + { 8.6919, 10.34 }, + { 9.9809, 11.103 }, + { 13.037, 9.3368 }, + { 13.514, 9.0498 }, + { 13.896, 8.6688 }, + { 14.135, 8.1908 }, + { 14.374, 7.7138 }, + { 14.517, 7.1888 }, + { 14.469, 6.6158 }, + { 14.421, 6.0898 }, + { 14.231, 5.5648 }, + { 13.896, 5.1358 }, + { 13.562, 4.7058 }, + { 13.132, 4.3718 }, + { 12.607, 4.1808 }, + { 12.607, 7.8088 }, + { 12.607, 7.9048 }, + { 12.607, 7.9998 }, + { 12.56, 8.0478 }, + { 12.56, 8.0478 }, + { 12.512, 8.1428 }, + { 12.416, 8.1908 } + }, + { + { 1.8649, 10.626 }, + { 2.1989, 11.199 }, + { 2.7249, 11.629 }, + { 3.3449, 11.867 }, + { 3.3449, 11.772 }, + { 3.3449, 8.2388 }, + { 3.3449, 8.1428 }, + { 3.3449, 8.0478 }, + { 3.3929, 7.9998 }, + { 3.4409, 7.9048 }, + { 3.4879, 7.8568 }, + { 3.5839, 7.8088 }, + { 7.3079, 5.6608 }, + { 6.0189, 4.8968 }, + { 2.9629, 6.6628 }, + { 2.2949, 7.0448 }, + { 1.8169, 7.6658 }, + { 1.6259, 8.3818 }, + { 1.4359, 9.0978 }, + { 1.4829, 9.9578 }, + { 1.8649, 10.626 } + }, + { + { 2.6769, 3.9898 }, + { 2.3429, 4.5628 }, + { 2.1989, 5.2308 }, + { 2.3429, 5.8988 }, + { 2.3429, 5.8988 }, + { 2.3899, 5.8518 }, + { 2.4379, 5.8518 }, + { 5.4939, 4.0848 }, + { 5.5889, 4.0378 }, + { 5.6369, 4.0378 }, + { 5.7319, 4.0378 }, + { 5.8279, 4.0378 }, + { 5.9229, 4.0378 }, + { 5.9709, 4.0848 }, + { 9.6949, 6.2338 }, + { 9.6949, 4.7538 }, + { 6.5919, 2.9388 }, + { 5.9229, 2.5568 }, + { 5.1589, 2.4618 }, + { 4.4429, 2.6528 }, + { 3.6789, 2.8438 }, + { 3.0589, 3.3208 }, + { 2.6769, 3.9898 } + }, + { + { 8.8359, 1.3638 }, + { 8.0719, 1.3638 }, + { 7.4989, 1.6028 }, + { 6.9739, 2.0318 }, + { 6.9739, 2.0318 }, + { 7.0209, 2.0798 }, + { 7.0689, 2.0798 }, + { 10.125, 3.8468 }, + { 10.22, 3.8938 }, + { 10.268, 3.9418 }, + { 10.316, 4.0378 }, + { 10.363, 4.1328 }, + { 10.363, 4.1808 }, + { 10.363, 4.2758 }, + { 10.363, 8.5728 }, + { 11.652, 7.8088 }, + { 11.652, 4.2758 }, + { 11.7, 2.6048 }, + { 10.363, 1.3638 }, + { 8.8359, 1.3638 } + }, + { + { 14.565, 9.3848 }, + { 14.756, 9.9098 }, + { 14.803, 10.435 }, + { 14.756, 10.96 }, + { 14.708, 11.485 }, + { 14.517, 12.011 }, + { 14.278, 12.488 }, + { 13.849, 13.204 }, + { 13.228, 13.777 }, + { 12.512, 14.111 }, + { 11.748, 14.445 }, + { 10.936, 14.541 }, + { 10.125, 14.35 }, + { 9.7429, 14.732 }, + { 9.3129, 15.066 }, + { 8.8359, 15.305 }, + { 8.3579, 15.543 }, + { 7.7849, 15.639 }, + { 7.2599, 15.639 }, + { 6.4479, 15.639 }, + { 5.6369, 15.4 }, + { 4.9679, 14.923 }, + { 4.2999, 14.445 }, + { 3.8229, 13.777 }, + { 3.5839, 13.013 }, + { 3.0109, 12.87 }, + { 2.5339, 12.631 }, + { 2.0559, 12.345 }, + { 1.6259, 12.011 }, + { 1.2919, 11.581 }, + { 1.0059, 11.151 }, + { 0.5759, 10.435 }, + { 0.4329, 9.6228 }, + { 0.5279, 8.8118 }, + { 0.6239, 7.9998 }, + { 0.9579, 7.2358 }, + { 1.4829, 6.6158 }, + { 1.2919, 6.0898 }, + { 1.2449, 5.5648 }, + { 1.2919, 5.0398 }, + { 1.3399, 4.5148 }, + { 1.5309, 3.9898 }, + { 1.7699, 3.5118 }, + { 2.1989, 2.7958 }, + { 2.8199, 2.2228 }, + { 3.5359, 1.8888 }, + { 4.2999, 1.5548 }, + { 5.1119, 1.4588 }, + { 5.9229, 1.6498 }, + { 6.3049, 1.2678 }, + { 6.7349, 0.9338 }, + { 7.2119, 0.6958 }, + { 7.6899, 0.4568 }, + { 8.2629, 0.3608 }, + { 8.7879, 0.3608 }, + { 9.5989, 0.3608 }, + { 10.411, 0.5998 }, + { 11.08, 1.0768 }, + { 11.748, 1.5548 }, + { 12.225, 2.2228 }, + { 12.464, 2.9868 }, + { 12.989, 3.0828 }, + { 13.514, 3.3208 }, + { 13.944, 3.6558 }, + { 14.374, 3.9898 }, + { 14.756, 4.3718 }, + { 14.994, 4.8488 }, + { 15.424, 5.5648 }, + { 15.567, 6.3768 }, + { 15.472, 7.1888 }, + { 15.376, 7.9998 }, + { 15.09, 8.7638 }, + { 14.565, 9.3848 } + } + } + ] + }, + FaceForm @ RGBColor[ 0.2, 0.2, 0.2, 1.0 ] + ] + }, + ImageSize -> { 17.0, 17.0 }, + PlotRange -> { { -0.5, 16.5 }, { -0.5, 16.5 } }, + AspectRatio -> Automatic +] \ No newline at end of file diff --git a/Developer/Resources/Icons/ServiceIconPaLM.wl b/Developer/Resources/Icons/ServiceIconPaLM.wl new file mode 100644 index 00000000..7d5c4463 --- /dev/null +++ b/Developer/Resources/Icons/ServiceIconPaLM.wl @@ -0,0 +1,118 @@ +Graphics[ + { + Thickness[ 0.0625 ], + Style[ + { + FilledCurve[ + { { { 1, 4, 3 }, { 0, 1, 0 }, { 1, 3, 3 }, { 1, 3, 3 }, { 0, 1, 0 }, { 0, 1, 0 }, { 1, 3, 3 } } }, + { + { + { 8.1487, 1.0 }, + { 10.039, 1.0 }, + { 11.62, 1.63 }, + { 12.775, 2.698 }, + { 10.523, 4.448 }, + { 9.8927, 4.027 }, + { 9.0937, 3.771 }, + { 8.1487, 3.771 }, + { 6.3227, 3.771 }, + { 4.7767, 5.002 }, + { 4.2227, 6.664 }, + { 1.9017, 6.664 }, + { 1.9017, 4.862 }, + { 3.0507, 2.575 }, + { 5.4127, 1.0 }, + { 8.1487, 1.0 } + } + } + ] + }, + FaceForm @ RGBColor[ 0.20392, 0.65882, 0.32549, 1.0 ] + ], + Style[ + { + FilledCurve[ + { { { 1, 4, 3 }, { 0, 1, 0 }, { 0, 1, 0 }, { 0, 1, 0 }, { 1, 3, 3 }, { 0, 1, 0 }, { 0, 1, 0 }, { 1, 3, 3 } } }, + { + { + { 14.851, 7.8425 }, + { 14.851, 8.3035 }, + { 14.81, 8.7405 }, + { 14.74, 9.1665 }, + { 8.1483, 9.1665 }, + { 8.1483, 6.5355 }, + { 11.923, 6.5355 }, + { 11.753, 5.6725 }, + { 11.258, 4.9435 }, + { 10.523, 4.4475 }, + { 10.523, 2.6975 }, + { 12.774, 2.6975 }, + { 14.093, 3.9165 }, + { 14.851, 5.7135 }, + { 14.851, 7.8425 } + } + } + ] + }, + FaceForm @ RGBColor[ 0.25882, 0.52157, 0.95686, 1.0 ] + ], + Style[ + { + FilledCurve[ + { { { 1, 4, 3 }, { 1, 3, 3 }, { 0, 1, 0 }, { 0, 1, 0 }, { 1, 3, 3 }, { 1, 3, 3 }, { 0, 1, 0 } } }, + { + { + { 4.2229, 6.6642 }, + { 4.0769, 7.0842 }, + { 4.0009, 7.5332 }, + { 4.0009, 8.0002 }, + { 4.0009, 8.4662 }, + { 4.0829, 8.9162 }, + { 4.2229, 9.3362 }, + { 4.2229, 11.138 }, + { 1.9009, 11.138 }, + { 1.4229, 10.193 }, + { 1.1489, 9.1312 }, + { 1.1489, 8.0002 }, + { 1.1489, 6.8682 }, + { 1.4229, 5.8062 }, + { 1.9009, 4.8622 }, + { 4.2229, 6.6642 } + } + } + ] + }, + FaceForm @ RGBColor[ 0.98431, 0.73725, 0.019608, 1.0 ] + ], + Style[ + { + FilledCurve[ + { { { 1, 4, 3 }, { 0, 1, 0 }, { 1, 3, 3 }, { 1, 3, 3 }, { 0, 1, 0 }, { 1, 3, 3 } } }, + { + { + { 8.1487, 12.229 }, + { 9.1817, 12.229 }, + { 10.103, 11.873 }, + { 10.832, 11.179 }, + { 12.827, 13.174 }, + { 11.62, 14.306 }, + { 10.039, 15.0 }, + { 8.1487, 15.0 }, + { 5.4127, 15.0 }, + { 3.0507, 13.425 }, + { 1.9017, 11.138 }, + { 4.2227, 9.3362 }, + { 4.7767, 10.998 }, + { 6.3227, 12.229 }, + { 8.1487, 12.229 } + } + } + ] + }, + FaceForm @ RGBColor[ 0.91765, 0.26275, 0.20784, 1.0 ] + ] + }, + ImageSize -> { 17.0, 17.0 }, + PlotRange -> { { -0.5, 16.5 }, { -0.5, 16.5 } }, + AspectRatio -> Automatic +] \ No newline at end of file diff --git a/FrontEnd/StyleSheets/Chatbook.nb b/FrontEnd/StyleSheets/Chatbook.nb index 0e952e2c..fb0dff3a 100644 --- a/FrontEnd/StyleSheets/Chatbook.nb +++ b/FrontEnd/StyleSheets/Chatbook.nb @@ -746,6 +746,11 @@ Notebook[ Magnification -> 1, FontSize -> 0.1 ], + PrivateCellOptions -> { + "AccentStyle" -> { + CellTrayWidgets -> <|"ChatIncluded" -> <|"Condition" -> True|>|> + } + }, TaggingRules -> <|"ChatNotebookSettings" -> <||>|>, CellTrayWidgets -> <| "GearMenu" -> <|"Condition" -> False|>, @@ -755,7 +760,7 @@ Notebook[ Cell[ BoxData[ DynamicBox[ - ToBoxes[Wolfram`Chatbook`$IncludedCellWidget, StandardForm], + ToBoxes[$IncludedCellWidget, StandardForm], SingleEvaluation -> True ] ], @@ -1152,16 +1157,11 @@ Notebook[ } ] } - |>, - PrivateCellOptions -> { - "AccentStyle" -> { - CellTrayWidgets -> <|"ChatIncluded" -> <|"Condition" -> True|>|> - } - } + |> ], Cell[ StyleData["ChatStyleSheetInformation"], - TaggingRules -> <|"StyleSheetVersion" -> "1.3.1.3910074547"|> + TaggingRules -> <|"StyleSheetVersion" -> "1.3.4.3910857306"|> ], Cell[ StyleData["Text"], @@ -11703,6 +11703,415 @@ Notebook[ ]) } ], + Cell[ + StyleData["ServiceIconAnthropic"], + TemplateBoxOptions -> { + DisplayFunction -> + (Function[ + GraphicsBox[ + { + Thickness[0.0625], + StyleBox[ + { + FilledCurveBox[ + { + { + {0, 2, 0}, + {0, 1, 0}, + {0, 1, 0}, + {0, 1, 0}, + {0, 1, 0}, + {0, 1, 0}, + {0, 1, 0}, + {0, 1, 0} + }, + {{0, 2, 0}, {0, 1, 0}, {0, 1, 0}} + }, + { + { + {5.0525, 13.543}, + {1.1665, 3.5431}, + {3.3395, 3.5431}, + {4.1345, 5.6431}, + {8.1995, 5.6431}, + {8.9945, 3.5431}, + {11.167, 3.5431}, + {7.2805, 13.543}, + {5.0525, 13.543} + }, + { + {6.1675, 11.015}, + {7.4975, 7.5011}, + {4.8375, 7.5011}, + {6.1675, 11.015} + } + } + ] + }, + {FaceForm[RGBColor[0.12157, 0.12157, 0.11765, 1.0]]}, + StripOnInput -> False + ], + StyleBox[ + { + FilledCurveBox[ + {{{0, 2, 0}, {0, 1, 0}, {0, 1, 0}, {0, 1, 0}}}, + { + { + {9.1665, 13.543}, + {13.042, 3.5432}, + {15.167, 3.5432}, + {11.293, 13.543}, + {9.1665, 13.543} + } + } + ] + }, + {FaceForm[RGBColor[0.12157, 0.12157, 0.11765, 1.0]]}, + StripOnInput -> False + ] + }, + ImageSize -> {17.0, 17.0}, + PlotRange -> {{-0.5, 16.5}, {-0.5, 16.5}}, + AspectRatio -> Automatic + ] + ]) + } + ], + Cell[ + StyleData["ServiceIconOpenAI"], + TemplateBoxOptions -> { + DisplayFunction -> + (Function[ + GraphicsBox[ + { + Thickness[0.0625], + StyleBox[ + { + FilledCurveBox[ + { + { + {0, 2, 0}, + {0, 1, 0}, + {0, 1, 0}, + {0, 1, 0}, + {0, 1, 0}, + {0, 1, 0} + }, + { + {0, 2, 0}, + {0, 1, 0}, + {1, 3, 3}, + {1, 3, 3}, + {1, 3, 3}, + {1, 3, 3}, + {1, 3, 3}, + {0, 1, 0}, + {1, 3, 3}, + {1, 3, 3}, + {0, 1, 0} + }, + { + {1, 4, 3}, + {0, 1, 0}, + {1, 3, 3}, + {1, 3, 3}, + {0, 1, 0}, + {0, 1, 0}, + {0, 1, 0}, + {1, 3, 3}, + {1, 3, 3}, + {1, 3, 3}, + {1, 3, 3} + }, + { + {0, 2, 0}, + {0, 1, 0}, + {0, 1, 0}, + {1, 3, 3}, + {1, 3, 3}, + {1, 3, 3}, + {1, 3, 3}, + {0, 1, 0}, + {1, 3, 3}, + {1, 3, 3} + }, + { + {1, 4, 3}, + {0, 1, 0}, + {0, 1, 0}, + {1, 3, 3}, + {1, 3, 3}, + {0, 1, 0}, + {0, 1, 0}, + {0, 1, 0}, + {1, 3, 3}, + {1, 3, 3} + }, + { + {1, 4, 3}, + {1, 3, 3}, + {0, 1, 0}, + {1, 3, 3}, + {1, 3, 3}, + {0, 1, 0}, + {0, 1, 0}, + {0, 1, 0}, + {1, 3, 3}, + {1, 3, 3} + }, + { + {1, 4, 3}, + {1, 3, 3}, + {0, 1, 0}, + {1, 3, 3}, + {1, 3, 3}, + {0, 1, 0}, + {0, 1, 0}, + {0, 1, 0}, + {1, 3, 3} + }, + { + {1, 4, 3}, + {1, 3, 3}, + {1, 3, 3}, + {1, 3, 3}, + {1, 3, 3}, + {1, 3, 3}, + {1, 3, 3}, + {1, 3, 3}, + {1, 3, 3}, + {1, 3, 3}, + {1, 3, 3}, + {1, 3, 3}, + {1, 3, 3}, + {1, 3, 3}, + {1, 3, 3}, + {1, 3, 3}, + {1, 3, 3}, + {1, 3, 3}, + {1, 3, 3}, + {1, 3, 3}, + {1, 3, 3}, + {1, 3, 3}, + {1, 3, 3}, + {1, 3, 3} + } + }, + { + { + {6.3529, 8.9548}, + {8.0239, 9.9098}, + {9.6949, 8.9548}, + {9.6949, 7.0448}, + {8.0239, 6.0898}, + {6.3529, 7.0448}, + {6.3529, 8.9548} + }, + CompressedData[ + "\n1:eJxTTMoPSmViYGCQAmIQrSj/JSdsr5iDwW51fu6tsg7CnxzPp00VdAhSX9C5\nIVEBzldla5zq3K0O53+65JskMEPDAcS9qi7kYMt1fXHBXk2HjQ9fTt3kI+ww\nayYIaDl0bQAKFIk4PP+98uOlXm0HkLEPNcUc3LZ9/nvFQsfh3uT21ihhCQdj\nENis41AZscL07G9JB8UNRRkTdXUdBI/v2tHrJuMw8W2NvWmcrsOqhJAg9QQ5\nuLzS32+lD2wUHBa5Ag0U0XWoSTQKNfBSdNhyomzf/Fk6Dt6RbRbXVJUcwvh0\nN819r43BB3GP8io5AF0P9IK2wy1poAlfFeH8R0Dv8GwUd2DSbhe76afhwJDf\nyHLUX9yh+cCpha5mGg5Mszik58mJO7CADJTVcGA92m9Y/lbMYbIEUOStugMs\nfKc5d+c8343gLwEZvxjBXzb7iMKGIgQfFh8AiR6qEA==\n " + ], + CompressedData[ + "\n1:eJxTTMoPSmViYGCQAmIQrRnTf+hrhrbDwVMLXbcZqzig8807HROeBmg72JvG\n7fL0UXHYIdf6OtACwT//PfjxUmlVB5F17g+rrqg7AEV5mF6rOEyWYAnje6vu\ncN+/d3reJQQ/X6j5wKmFCH6hLdf1xQUIPgMIOCD4jVOdu3PUVeDmz+KQnheX\nKengplrKNKtDGc6PsNxyoqxOzUGjrmdn9kslhzUyUSnW8loOzBXcKhr3lB26\nc57/XrlRC+4+kLcuPNJyWPXxkm+SgBqcX75vvpS+rDqc7wLSqKnhIK1/V4Wt\nUctBHuj9HXKaDntKgC68punwrgYYEr80HS4q3f5Zp6XpcBoYbJ/3ajkwabeL\n3fTTcAA5a5+8toO6IQfQSeoOK455m3c2ajvcPAcMuFQ1iPgsbQdgKAk1O6hi\nhD8ARCyk8Q==\n " + ], + CompressedData[ + "\n1:eJxTTMoPSmViYGAQB2IQvch12+e/VzQcgtQXdG5IVHDIM2nY7pCk6LDO/WGV\nyDoVh69ekW0W35Qdbv+sy9pjouaQ+/z3yo9CWg6vpm7iKVyj5LDLk4dJm13b\noXbdtqR6SSWHGXlCzQdOaTvoKsp/yQlTdGh9HbhDzlUHbn5xxsS3Nft1HDi7\n5JPf3ZJzSBKIsNzCoeuQ/6H1ZMhBGYfHS2cfUfig43CjsdhtSpmUQ4r1ff/e\n6zoOKjv/tH+JlnAAGr7QtUzHAaQ9ykkMbt8b/d3q/N0iDpZbTpTtk9d2MBE0\ns9l7Scjhrgpb41RnLYeKOYuUd9YIOoCsO2Gm6TCrHCQgAOe/YgHpkIfzn61T\nfdI8D8E/rmk16fR/eQd5sIc0HZLrb9pWSihg8BdI6QOt1HS4vOexiKynggN6\n+AIA6SqZow==\n " + ], + CompressedData[ + "\n1:eJxTTMoPSmViYGAQBWIQnfb9SeLCa3/te6fnCTU7qDropEo+ipjO6HDz3Pfg\nx6lqDlO+scXPOMPqYBq3y5PHSd2hSz75XdQhLodpzt05z3cj+KpsjVOduxH8\nixNj/jlXKcD5l/c8FpH1RPCT62/aVkooOLSdDDm4QoXb4bim1aTT/+Udmord\npnxr43Z4tk71SfM8eQeP/bWyFs+5HV7cXPMrJlfewUE48fDl1TwOr1hMBM1s\n5B3eHLBU9rKWhZizRMzh3uT21ihhCQeg5N6gacIOoj1er1i2sDvsVufn3rpM\nykFl55/2L9FMDmWF0rwPdGUc8hYz7mEV+msPlKw8vlLO4Sf/y+3rmX/ZHwQa\nW31YweG9hat70c9v9n8kiq8LGSk51F7YHPl153f7reY/DqW8UnZADz8Aqo+U\nXg==\n " + ], + CompressedData[ + "\n1:eJxTTMoPSmViYGAQB2IQPcNHtMcri9WhaqmOs8xrfgeF5HdRTvuYHEIPrlji\n5yDkoJMq+ShiOqPDuVXnr4a9EYHLu035xhY/QxyD/2yd6pNmOWYHkLBdhrjD\nowjx7RcbEHyXX29fH/gp6jD/LMhAAQfVUqZZHNFiDrvV+bm3qgk4KHtVN+v3\nIPisR/sNy98i+Az5jSxH/cXh/Ecvp27i2YjgP9jHN8f4kTjcfLHfp9+dTFZ2\nkLVId8l8LwHnG4EcyizsALJeOk7K4f4D7skrm9jh5mX5fu4LLmFxyA2rXbdt\nkYjDivBTRkc2Mjt8m353cvtRQYekhddM3luwOjBzdskn5/E6yLx+ZCZ1gM2B\n94HuhAUVHA4hJSrT/0/gckAPXwAX85Sr\n " + ], + CompressedData[ + "\n1:eJxTTMoPSmViYGAQAWIQ/bp4q+jv1YoOXX1PPslf+mpvoLVS+IKKApx/8qn9\nkvv/ZB2+lz6YI7j0p72BzzIut6fSDuZSB6IVHBkc0PnCnxzPp4nKOBgf2aiX\nt5jBQfD4rh29bgg+Awg4qDjsYRUSsT/G51Boy3V9cYGKQ3Og59wGNX6HD8uP\neZt3qjjU/7YqONfB75Av1Hzg1EIVh93q/Nxb1QQcEp5eULq9U8VhziLlnX/a\nEfxZ5SARBL/m04aAbClBOB/sTlVFh+e/V3685Kvu8IrFRNDMRh7Oh6lPAwN1\nh7TvTxIXXmOB64eFB3p4AQDL0Y6N\n " + ], + CompressedData[ + "\n1:eJxdVHtQVGUUXwlWopV3y8Iswt1dYJfdu5thBPj4fomCmIo8SiW0knZKR1rk\nYQ4SDeGKUYKISAUFoeE4OEpoKYVJFpPPRsQJbEeeatEq7Y5Ly2OB7t2dvX/0\nzdz55nzfOeee3+/8zkdt06VqXXg8XhLzsftQof/pRIrGdp6uxLVLgg0Ha9/1\nLaURfXPJ+u5uKVa88eCWpI5GiN6YcqFfxt0/SrmwUG8MQ7fEMFm8gwZrpUyE\nY5v3pthz7jR8SzuvfeUmR0G1yPXVChXYNIZJOZrrfgltbVOintly34kEG92R\nH4k/p0+abx9UojFIc0/GVyDhuyczd2JUsIcVR+B4zjKP3hEVTokz3loyEIam\nVYyDPw0euyBDFLvOqlCjPZC1pUgKtowru2nE/t6VvbhRAh1bEKWGMe/bZ6db\nKGRWXh6X16vhXRjdsvx8KDrymUKFGhzQZ/R0SEPwfZLARZmowZixM1bqEczZ\ne0s1a5uvBXK2dA1z8okQN2+wS41Di96jqQE/fMCgqu6jEbB6g00U5cPVb+W/\n/unaGk8OL/ze/LmnRQC67Yt/TvAj4RO99GKq0B2M97Gciwr8cWoqM3uVq4P3\neAWyu2bb9ubysIt1aJVj0mv0/JmnpoiTb/dlda80tFgIS98eRQQ8f3zus0iR\nibCsJa8Lx+b9MQwjw8TZz0ue9VFN5wzk6gNyfGC5FDv6d5VX3B8kwexBA4Uk\n9Rw18+8I+VURd/j6XAhUdz5/GHxijKQdpSoKzGK8f+vs5vF2K+kryUs4sjuI\n+7+s3VZmeU2Ewq9V8WLjE1IekjWWsULI3Zv0V9N/kvuDV1U8HZczTjY+0vwQ\n4eWLfFnt3KHiCeKI88LQM9UnP0yxEQcOAVTawOFNtfMQ+pI568YWPuxxlXyw\n1stX5mHldp1JnySA2bKGgTpLnPyzKAoGJ0h569BoTa6/o+8brWR4tKZN8E0A\n9i1IPnNEO0VYNl6MCUQdg/Kv1RaSnhrR+JEpCOzWOvSYmIRMwj4x1ndXZc7G\nPyTNHglhBZcX4m/XxUzr7pGGpQxD+0MddQb0kp1PTza+XU1xtig8ze3Y81LO\nHkhmGntbBnb6KheNEIVdmOFg3Q7HmYlT/8767TrPk3N4KWaKqh7LYSif0Vrv\nz8dYEXlh65QCPf2DDHPuDp3OVyLdTqwHAu7+Zk0bUcKlw83XnyxAHhNddEkF\nJ9/O+d5T3yRtL/KBPb2NtstUqfUDk61MeFcNZz9tjIzXSTSYKbMYeksC8fFO\nVtlq6OwNFsOerlMNp35OJzIvjlqNL7cqrnuXUfj/+/Mf6Ef9+w==\n " + ] + } + ] + }, + {FaceForm[RGBColor[0.2, 0.2, 0.2, 1.0]]}, + StripOnInput -> False + ] + }, + ImageSize -> {17.0, 17.0}, + PlotRange -> {{-0.5, 16.5}, {-0.5, 16.5}}, + AspectRatio -> Automatic + ] + ]) + } + ], + Cell[ + StyleData["ServiceIconPaLM"], + TemplateBoxOptions -> { + DisplayFunction -> + (Function[ + GraphicsBox[ + { + Thickness[0.0625], + StyleBox[ + { + FilledCurveBox[ + { + { + {1, 4, 3}, + {0, 1, 0}, + {1, 3, 3}, + {1, 3, 3}, + {0, 1, 0}, + {0, 1, 0}, + {1, 3, 3} + } + }, + { + { + {8.1487, 1.0}, + {10.039, 1.0}, + {11.62, 1.63}, + {12.775, 2.698}, + {10.523, 4.448}, + {9.8927, 4.027}, + {9.0937, 3.771}, + {8.1487, 3.771}, + {6.3227, 3.771}, + {4.7767, 5.002}, + {4.2227, 6.664}, + {1.9017, 6.664}, + {1.9017, 4.862}, + {3.0507, 2.575}, + {5.4127, 1.0}, + {8.1487, 1.0} + } + } + ] + }, + {FaceForm[RGBColor[0.20392, 0.65882, 0.32549, 1.0]]}, + StripOnInput -> False + ], + StyleBox[ + { + FilledCurveBox[ + { + { + {1, 4, 3}, + {0, 1, 0}, + {0, 1, 0}, + {0, 1, 0}, + {1, 3, 3}, + {0, 1, 0}, + {0, 1, 0}, + {1, 3, 3} + } + }, + { + { + {14.851, 7.8425}, + {14.851, 8.3035}, + {14.81, 8.7405}, + {14.74, 9.1665}, + {8.1483, 9.1665}, + {8.1483, 6.5355}, + {11.923, 6.5355}, + {11.753, 5.6725}, + {11.258, 4.9435}, + {10.523, 4.4475}, + {10.523, 2.6975}, + {12.774, 2.6975}, + {14.093, 3.9165}, + {14.851, 5.7135}, + {14.851, 7.8425} + } + } + ] + }, + {FaceForm[RGBColor[0.25882, 0.52157, 0.95686, 1.0]]}, + StripOnInput -> False + ], + StyleBox[ + { + FilledCurveBox[ + { + { + {1, 4, 3}, + {1, 3, 3}, + {0, 1, 0}, + {0, 1, 0}, + {1, 3, 3}, + {1, 3, 3}, + {0, 1, 0} + } + }, + { + { + {4.2229, 6.6642}, + {4.0769, 7.0842}, + {4.0009, 7.5332}, + {4.0009, 8.0002}, + {4.0009, 8.4662}, + {4.0829, 8.9162}, + {4.2229, 9.3362}, + {4.2229, 11.138}, + {1.9009, 11.138}, + {1.4229, 10.193}, + {1.1489, 9.1312}, + {1.1489, 8.0002}, + {1.1489, 6.8682}, + {1.4229, 5.8062}, + {1.9009, 4.8622}, + {4.2229, 6.6642} + } + } + ] + }, + {FaceForm[RGBColor[0.98431, 0.73725, 0.019608, 1.0]]}, + StripOnInput -> False + ], + StyleBox[ + { + FilledCurveBox[ + { + { + {1, 4, 3}, + {0, 1, 0}, + {1, 3, 3}, + {1, 3, 3}, + {0, 1, 0}, + {1, 3, 3} + } + }, + { + { + {8.1487, 12.229}, + {9.1817, 12.229}, + {10.103, 11.873}, + {10.832, 11.179}, + {12.827, 13.174}, + {11.62, 14.306}, + {10.039, 15.0}, + {8.1487, 15.0}, + {5.4127, 15.0}, + {3.0507, 13.425}, + {1.9017, 11.138}, + {4.2227, 9.3362}, + {4.7767, 10.998}, + {6.3227, 12.229}, + {8.1487, 12.229} + } + } + ] + }, + {FaceForm[RGBColor[0.91765, 0.26275, 0.20784, 1.0]]}, + StripOnInput -> False + ] + }, + ImageSize -> {17.0, 17.0}, + PlotRange -> {{-0.5, 16.5}, {-0.5, 16.5}}, + AspectRatio -> Automatic + ] + ]) + } + ], Cell[ StyleData["SideChatIcon"], TemplateBoxOptions -> { From 04debb68771cc5c55f5910dcd713a69057274ce6 Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Wed, 6 Dec 2023 13:18:39 -0500 Subject: [PATCH 07/50] Add service icons to menu and fix magnification of menus --- Source/Chatbook/Menus.wl | 16 +++- Source/Chatbook/Models.wl | 35 +++++-- Source/Chatbook/UI.wl | 186 ++++++++++++++++++++++++++++---------- 3 files changed, 177 insertions(+), 60 deletions(-) diff --git a/Source/Chatbook/Menus.wl b/Source/Chatbook/Menus.wl index dd5156e2..9298af75 100644 --- a/Source/Chatbook/Menus.wl +++ b/Source/Chatbook/Menus.wl @@ -12,6 +12,7 @@ BeginPackage[ "Wolfram`Chatbook`Menus`" ]; HoldComplete[ `AttachSubmenu; `MakeMenu; + `menuMagnification; `removeChatMenus; ]; @@ -74,10 +75,10 @@ MakeMenu // endDefinition; (*menuItem*) menuItem // beginDefinition; -menuItem[ spec: KeyValuePattern[ "Content" -> content_ ] ] := - menuItem @ <| spec, "Content" :> content |>; +menuItem[ spec: KeyValuePattern[ "Data" -> content_ ] ] := + menuItem @ <| spec, "Data" :> content |>; -menuItem[ spec: KeyValuePattern @ { "Type" -> "Submenu", "Content" :> content_ } ] := +menuItem[ spec: KeyValuePattern @ { "Type" -> "Submenu", "Data" :> content_ } ] := EventHandler[ menuItem[ Lookup[ spec, "Icon", Spacer[ 0 ] ], @@ -182,6 +183,15 @@ AttachSubmenu[ parentMenu_, expr: Except[ _Cell ] ] := AttachSubmenu[ expr_ ] := AttachSubmenu[ EvaluationCell[ ], expr ]; +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*menuMagnification*) +menuMagnification // beginDefinition; +menuMagnification[ obj_ ] := menuMagnification[ $OperatingSystem, AbsoluteCurrentValue[ obj, Magnification ] ]; +menuMagnification[ "Windows", magnification_? NumberQ ] := Min[ magnification * 0.75, 1.5 ]; +menuMagnification[ _, magnification_ ] := magnification; +menuMagnification // endDefinition; + (* ::**************************************************************************************************************:: *) (* ::Subsection::Closed:: *) (*determineAttachmentPosition*) diff --git a/Source/Chatbook/Models.wl b/Source/Chatbook/Models.wl index 0a9b8b93..ef80207c 100644 --- a/Source/Chatbook/Models.wl +++ b/Source/Chatbook/Models.wl @@ -17,9 +17,10 @@ BeginPackage[ "Wolfram`Chatbook`Models`" ]; Begin[ "`Private`" ]; Needs[ "Wolfram`Chatbook`" ]; -Needs[ "Wolfram`Chatbook`Common`" ]; Needs[ "Wolfram`Chatbook`Actions`" ]; +Needs[ "Wolfram`Chatbook`Common`" ]; Needs[ "Wolfram`Chatbook`Dynamics`" ]; +Needs[ "Wolfram`Chatbook`UI`" ]; (* ::**************************************************************************************************************:: *) (* ::Section::Closed:: *) @@ -267,13 +268,31 @@ fineTunedModelName // endDefinition; (* ::Subsection::Closed:: *) (*modelIcon*) modelIcon // beginDefinition; -modelIcon[ KeyValuePattern[ "Icon" -> icon_ ] ] := icon; -modelIcon[ KeyValuePattern[ "Name" -> name_String ] ] := modelIcon @ name; -modelIcon[ name0_String ] := With[ { name = toModelName @ name0 }, modelIcon @ name /; name =!= name0 ]; -modelIcon[ name_String ] /; StringStartsQ[ name, "ft:" ] := modelIcon @ StringDelete[ name, StartOfString~~"ft:" ]; -modelIcon[ gpt_String ] /; StringStartsQ[ gpt, "gpt-3.5" ] := RawBoxes @ TemplateBox[ { }, "ModelGPT35" ]; -modelIcon[ gpt_String ] /; StringStartsQ[ gpt, "gpt-4" ] := RawBoxes @ TemplateBox[ { }, "ModelGPT4" ]; -modelIcon[ name_String ] := $defaultModelIcon; + +modelIcon[ KeyValuePattern[ "Icon" -> icon_ ] ] := + icon; + +modelIcon[ KeyValuePattern @ { "Name" -> name_String, "Service" -> service_String } ] := + Replace[ modelIcon @ name, $defaultModelIcon :> serviceIcon @ service ]; + +modelIcon[ KeyValuePattern[ "Name" -> name_String ] ] := + modelIcon @ name; + +modelIcon[ name0_String ] := + With[ { name = toModelName @ name0 }, modelIcon @ name /; name =!= name0 ]; + +modelIcon[ name_String ] /; StringStartsQ[ name, "ft:" ] := + modelIcon @ StringDelete[ name, StartOfString~~"ft:" ]; + +modelIcon[ gpt_String ] /; StringStartsQ[ gpt, "gpt-3.5" ] := + RawBoxes @ TemplateBox[ { }, "ModelGPT35" ]; + +modelIcon[ gpt_String ] /; StringStartsQ[ gpt, "gpt-4" ] := + RawBoxes @ TemplateBox[ { }, "ModelGPT4" ]; + +modelIcon[ name_String ] := + $defaultModelIcon; + modelIcon // endDefinition; (* ::**************************************************************************************************************:: *) diff --git a/Source/Chatbook/UI.wl b/Source/Chatbook/UI.wl index 552c131d..c9cf0ffa 100644 --- a/Source/Chatbook/UI.wl +++ b/Source/Chatbook/UI.wl @@ -26,6 +26,7 @@ CreateToolbarContent[] is called by the NotebookToolbar to generate the content `getPersonaMenuIcon; `personaDisplayName; `resizeMenuIcon; +`serviceIcon; Begin["`Private`"] @@ -106,6 +107,7 @@ $cloudModelChooser := PopupMenu[ {modelName, settings} |-> ( modelName -> Grid[{{getModelMenuIcon[settings], modelDisplayName[modelName]}}] ), + (* FIXME: use the new system *) getModelsMenuItems[] ], ImageSize -> {Automatic, 30}, @@ -1223,16 +1225,16 @@ makeChatActionMenuContent[ {alignedMenuIcon[getIcon["ToolManagerRepository"]], "Add & Manage Tools\[Ellipsis]", "ToolManage"}, Delimiter, <| - "Label" -> "Models", - "Type" -> "Submenu", - "Icon" -> alignedMenuIcon @ getIcon[ "ChatBlockSettingsMenuIcon" ], - "Content" :> createServiceMenu[ targetObj, ParentCell @ EvaluationCell[ ] ] + "Label" -> "Models", + "Type" -> "Submenu", + "Icon" -> alignedMenuIcon @ getIcon[ "ChatBlockSettingsMenuIcon" ], + "Data" :> createServiceMenu[ targetObj, ParentCell @ EvaluationCell[ ] ] |>, <| - "Label" -> "Advanced Settings", - "Type" -> "Submenu", - "Icon" -> alignedMenuIcon @ getIcon[ "AdvancedSettings" ], - "Content" -> advancedSettingsMenu + "Label" -> "Advanced Settings", + "Type" -> "Submenu", + "Icon" -> alignedMenuIcon @ getIcon[ "AdvancedSettings" ], + "Data" -> advancedSettingsMenu |> } ]; @@ -1240,20 +1242,38 @@ makeChatActionMenuContent[ Replace[ format, { - "List" :> menuItems - , - "Expression" :> MakeMenu[ menuItems, GrayLevel[ 0.85 ], $chatMenuWidth ] - , - "Cell"|Automatic :> Cell[ - BoxData @ ToBoxes @ MakeMenu[ menuItems, GrayLevel[ 0.85 ], $chatMenuWidth ], - "AttachedChatMenu" - ] - , - expr_ :> throwInternalFailure[ makeChatActionMenuContent, expr ] + "List" :> menuItems, + "Expression" :> makeChatMenuExpression @ menuItems, + "Cell" :> makeChatMenuCell[ menuItems, menuMagnification @ targetObj ], + expr_ :> throwInternalFailure[ makeChatActionMenuContent, expr ] } ] ]]; +(* ::**************************************************************************************************************:: *) +(* ::Subsubsubsection::Closed:: *) +(*makeChatMenuExpression*) +makeChatMenuExpression // beginDefinition; +makeChatMenuExpression[ menuItems_ ] := MakeMenu[ menuItems, GrayLevel[ 0.85 ], $chatMenuWidth ]; +makeChatMenuExpression // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsubsection::Closed:: *) +(*makeChatMenuCell*) +makeChatMenuCell // beginDefinition; + +makeChatMenuCell[ menuItems_ ] := + makeChatMenuCell[ menuItems, CurrentValue[ Magnification ] ]; + +makeChatMenuCell[ menuItems_, magnification_ ] := + Cell[ + BoxData @ ToBoxes @ makeChatMenuExpression @ menuItems, + "AttachedChatMenu", + Magnification -> magnification + ]; + +makeChatMenuCell // endDefinition; + (* ::**************************************************************************************************************:: *) (* ::Subsubsection::Closed:: *) (*getIcon*) @@ -1276,7 +1296,7 @@ createServiceMenu[ obj_, root_ ] := (createServiceItem[ obj, model, root, #1 ] &) /@ getAvailableServiceNames[ ] ], GrayLevel[ 0.85 ], - 120 + 140 ] ]; @@ -1288,22 +1308,37 @@ createServiceMenu // endDefinition; createServiceItem // beginDefinition; createServiceItem[ obj_, model_, root_, service_String ] := <| - "Type" -> "Submenu", - "Label" -> service, - "Icon" -> serviceSelectionCheckmark[ model, service ], - "Content" :> dynamicModelMenu[ obj, root, model, service ] + "Type" -> "Submenu", + "Label" -> service, + "Icon" -> serviceIcon[ model, service ], + "Data" :> dynamicModelMenu[ obj, root, model, service ] |>; createServiceItem // endDefinition; (* ::**************************************************************************************************************:: *) (* ::Subsubsection::Closed:: *) -(*serviceSelectionCheckmark*) -serviceSelectionCheckmark // beginDefinition; -serviceSelectionCheckmark[ KeyValuePattern[ "Service" -> service_String ], service_String ] := $currentSelectionCheck; -serviceSelectionCheckmark[ _String, "OpenAI" ] := $currentSelectionCheck; -serviceSelectionCheckmark[ _, _ ] := Style[ $currentSelectionCheck, ShowContents -> False ]; -serviceSelectionCheckmark // endDefinition; +(*serviceIcon*) +serviceIcon // beginDefinition; + +serviceIcon[ KeyValuePattern[ "Service" -> service_String ], service_String ] := + alignedMenuIcon[ $currentSelectionCheck, serviceIcon @ service ]; + +serviceIcon[ _String, "OpenAI" ] := + alignedMenuIcon[ $currentSelectionCheck, serviceIcon @ "OpenAI" ]; + +serviceIcon[ _, service_String ] := + alignedMenuIcon[ Style[ $currentSelectionCheck, ShowContents -> False ], serviceIcon @ service ]; + +serviceIcon[ KeyValuePattern[ "Service" -> service_String ] ] := + serviceIcon @ service; + +serviceIcon[ "OpenAI" ] := chatbookIcon[ "ServiceIconOpenAI" , True ]; +serviceIcon[ "Anthropic" ] := chatbookIcon[ "ServiceIconAnthropic", True ]; +serviceIcon[ "PaLM" ] := chatbookIcon[ "ServiceIconPaLM" , True ]; +serviceIcon[ service_String ] := ""; + +serviceIcon // endDefinition; $currentSelectionCheck = Style[ "\[Checkmark]", FontColor -> GrayLevel[ 0.25 ] ]; @@ -1339,7 +1374,7 @@ dynamicModelMenu[ obj_, root_, model_, service_ ] := Dynamic[ display, TrackedSymbols :> { display } ], Initialization :> Quiet[ Needs[ "Wolfram`Chatbook`" -> None ]; - display = makeServiceModelMenu[ obj, root, model, service ] + display = catchAlways @ makeServiceModelMenu[ obj, root, model, service ] ], SynchronousInitialization -> False ]; @@ -1351,28 +1386,81 @@ dynamicModelMenu // endDefinition; (*makeServiceModelMenu*) makeServiceModelMenu // beginDefinition; -makeServiceModelMenu[ obj_, root_, model_, service_String ] := - makeServiceModelMenu[ obj, root, model, service, getServiceModelList @ service ]; - -makeServiceModelMenu[ obj_, root_, model_, service_String, models_List ] := - MakeMenu[ - Join[ - { service }, - Map[ - Function @ { - alignedMenuIcon[ modelSelectionCheckmark[ model, #Name ], #Icon ], - #DisplayName, - Hold[ removeChatMenus @ root; setModel[ obj, #1 ] ] - }, - Union @ models - ] - ], - GrayLevel[ 0.85 ], - 280 - ]; +makeServiceModelMenu[ obj_, root_, currentModel_, service_String ] := + makeServiceModelMenu[ obj, root, currentModel, service, getServiceModelList @ service ]; + +makeServiceModelMenu[ obj_, root_, currentModel_, service_String, models_List ] := + MakeMenu[ Join[ { service }, groupMenuModels[ obj, root, currentModel, models ] ], GrayLevel[ 0.85 ], 280 ]; makeServiceModelMenu // endDefinition; +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*groupMenuModels*) +groupMenuModels // beginDefinition; + +groupMenuModels[ obj_, root_, currentModel_, models_List ] := + groupMenuModels[ obj, root, currentModel, GroupBy[ models, modelGroupName ] ]; + +groupMenuModels[ obj_, root_, currentModel_, models_Association ] /; Length @ models === 1 := + modelMenuItem[ obj, root, currentModel ] /@ First @ models; + +groupMenuModels[ obj_, root_, currentModel_, models_Association ] := + Flatten[ KeyValueMap[ menuModelGroup[ obj, root, currentModel ], models ], 1 ]; + +groupMenuModels // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*menuModelGroup*) +menuModelGroup // beginDefinition; + +menuModelGroup[ obj_, root_, currentModel_ ] := + menuModelGroup[ obj, root, currentModel, ## ] &; + +menuModelGroup[ obj_, root_, currentModel_, None, models_List ] := + modelMenuItem[ obj, root, currentModel ] /@ models; + +menuModelGroup[ obj_, root_, currentModel_, "Snapshot Models", models_List ] := + If[ TrueQ @ showSnapshotModelsQ[ ], + Join[ { "Snapshot Models" }, modelMenuItem[ obj, root, currentModel ] /@ models ], + { } + ]; + +menuModelGroup[ obj_, root_, currentModel_, name_String, models_List ] := + Join[ { name }, modelMenuItem[ obj, root, currentModel ] /@ models ]; + +menuModelGroup // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*modelGroupName*) +modelGroupName // beginDefinition; +modelGroupName[ KeyValuePattern[ "FineTuned" -> True ] ] := "Fine Tuned Models"; +modelGroupName[ KeyValuePattern[ "Snapshot" -> True ] ] := "Snapshot Models"; +modelGroupName[ _ ] := None; +modelGroupName // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*modelMenuItem*) +modelMenuItem // beginDefinition; + +modelMenuItem[ obj_, root_, currentModel_ ] := modelMenuItem[ obj, root, currentModel, #1 ] &; + +modelMenuItem[ + obj_, + root_, + currentModel_, + model: KeyValuePattern @ { "Name" -> name_, "Icon" -> icon_, "DisplayName" -> displayName_ } +] := { + alignedMenuIcon[ modelSelectionCheckmark[ currentModel, name ], icon ], + displayName, + Hold[ removeChatMenus @ root; setModel[ obj, model ] ] +}; + +modelMenuItem // endDefinition; + (* ::**************************************************************************************************************:: *) (* ::Subsubsection::Closed:: *) (*modelSelectionCheckmark*) From 0c56bab723179627e50c85ef2de8ef68f2ed00c5 Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Wed, 6 Dec 2023 13:19:49 -0500 Subject: [PATCH 08/50] Increment paclet version --- PacletInfo.wl | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/PacletInfo.wl b/PacletInfo.wl index 4c060cdd..304048e8 100644 --- a/PacletInfo.wl +++ b/PacletInfo.wl @@ -1,7 +1,7 @@ PacletObject[ <| "Name" -> "Wolfram/Chatbook", "PublisherID" -> "Wolfram", - "Version" -> "1.3.3", + "Version" -> "1.3.4", "WolframVersion" -> "13.3+", "Description" -> "Wolfram Notebooks + LLMs", "License" -> "MIT", From 72c9cbbb940b639c8da98a415ebbca0ea395616e Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Thu, 7 Dec 2023 08:00:50 -0500 Subject: [PATCH 09/50] Created preferences tab view --- Source/Chatbook/Dynamics.wl | 9 +- Source/Chatbook/PreferencesContent.wl | 405 ++++++++++++++++++++++++++ Source/Chatbook/UI.wl | 322 ++------------------ 3 files changed, 442 insertions(+), 294 deletions(-) create mode 100644 Source/Chatbook/PreferencesContent.wl diff --git a/Source/Chatbook/Dynamics.wl b/Source/Chatbook/Dynamics.wl index 23b1b099..08211606 100644 --- a/Source/Chatbook/Dynamics.wl +++ b/Source/Chatbook/Dynamics.wl @@ -17,10 +17,11 @@ Needs[ "Wolfram`Chatbook`Common`" ]; (* ::Section::Closed:: *) (*Configuration*) $dynamicTriggers = <| - "ChatBlock" :> $chatBlockTrigger, - "Models" :> $modelsTrigger, - "Personas" :> $personasTrigger, - "Tools" :> $toolsTrigger + "ChatBlock" :> $chatBlockTrigger, + "Models" :> $modelsTrigger, + "Personas" :> $personasTrigger, + "Preferences" :> $preferencesTrigger, + "Tools" :> $toolsTrigger |>; Cases[ $dynamicTriggers, sym_Symbol :> (sym = 0) ]; diff --git a/Source/Chatbook/PreferencesContent.wl b/Source/Chatbook/PreferencesContent.wl new file mode 100644 index 00000000..48c7b27c --- /dev/null +++ b/Source/Chatbook/PreferencesContent.wl @@ -0,0 +1,405 @@ +(* ::Section::Closed:: *) +(*Package Header*) +BeginPackage[ "Wolfram`Chatbook`PreferencesContent`" ]; + +HoldComplete[ + `createPreferencesContent; + `openPreferencesPage; +]; + +Begin[ "`Private`" ]; + +Needs[ "Wolfram`Chatbook`" ]; +Needs[ "Wolfram`Chatbook`Common`" ]; +Needs[ "Wolfram`Chatbook`Personas`" ]; +Needs[ "Wolfram`Chatbook`UI`" ]; +Needs[ "Wolfram`Chatbook`Errors`" ]; +Needs[ "Wolfram`Chatbook`PreferencesUtils`" ]; +Needs[ "Wolfram`Chatbook`Settings`" ]; +Needs[ "Wolfram`Chatbook`Models`" ]; +Needs[ "Wolfram`Chatbook`Services`" ]; +Needs[ "Wolfram`Chatbook`Dynamics`" ]; +Needs[ "Wolfram`Chatbook`ToolManager`" ]; +Needs[ "Wolfram`Chatbook`PersonaManager`" ]; + +(* ::**************************************************************************************************************:: *) +(* ::Section::Closed:: *) +(*Configuration*) +$verticalSpacer = { Pane[ "", ImageSize -> { Automatic, 20 } ], SpanFromLeft }; +$preferencesPages = { "Notebooks", "Services", "Personas", "Tools" }; +$$preferencesPage = Alternatives @@ $preferencesPages; + +(* ::**************************************************************************************************************:: *) +(* ::Section::Closed:: *) +(*Content*) + +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*createPreferencesContent*) +createPreferencesContent[ ] := Enclose[ + Module[ { notebookSettings, serviceSettings, personaSettings, toolSettings, tabView, reset }, + + notebookSettings = ConfirmMatch[ preferencesContent[ "Notebooks" ], _Dynamic|_DynamicModule, "Notebooks" ]; + serviceSettings = ConfirmMatch[ preferencesContent[ "Services" ], _Dynamic|_DynamicModule, "Services" ]; + personaSettings = ConfirmMatch[ preferencesContent[ "Personas" ], _Dynamic|_DynamicModule, "Personas" ]; + toolSettings = ConfirmMatch[ preferencesContent[ "Tools" ], _Dynamic|_DynamicModule, "Tools" ]; + + tabView = TabView[ + { + { "Notebooks", "Notebooks" -> notebookSettings }, + { "Services" , "Services" -> serviceSettings }, + { "Personas" , "Personas" -> personaSettings }, + { "Tools" , "Tools" -> toolSettings } + }, + Dynamic @ CurrentValue[ + $FrontEnd, + { PrivateFrontEndOptions, "InterfaceSettings", "Chatbook", "PreferencesTab" }, + "Notebooks" + ], + Background -> None, + FrameMargins -> { { 2, 2 }, { 2, 3 } }, + ImageMargins -> { { 10, 10 }, { 2, 2 } }, + ImageSize -> { 640, Automatic }, + LabelStyle -> "feTabView" + ]; + + reset = Pane[ $resetButton, ImageMargins -> { { 20, 0 }, { 0, 10 } }, ImageSize -> 640 ]; + + Grid[ + { + $verticalSpacer, + { tabView, "" }, + $verticalSpacer, + { reset, SpanFromLeft }, + $verticalSpacer + }, + Alignment -> Left, + BaseStyle -> "defaultGrid", + AutoDelete -> False, + FrameStyle -> { AbsoluteThickness[ 1 ], GrayLevel[ 0.898 ] }, + Dividers -> { False, { 4 -> True } }, + Spacings -> { 0, 0.7 } + ] + ], + throwInternalFailure +]; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*preferencesContent*) +preferencesContent // beginDefinition; +preferencesContent[ "Notebooks" ] := trackedDynamic[ notebookSettingsPanel[ ], { "Models" } ]; +preferencesContent[ "Personas" ] := trackedDynamic[ personaSettingsPanel[ ], { "Personas" } ]; +preferencesContent[ "Services" ] := trackedDynamic[ "Coming soon.", { "Models" } ]; +preferencesContent[ "Tools" ] := toolSettingsPanel[ ]; +preferencesContent // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*notebookSettingsPanel*) +notebookSettingsPanel // beginDefinition; + +notebookSettingsPanel[ ] := Pane[ + DynamicModule[ + { display = ProgressIndicator[ Appearance -> "Percolate" ] }, + Dynamic[ display ], + Initialization :> (display = makeFrontEndAndNotebookSettingsContent @ $FrontEnd), + SynchronousInitialization -> False + ], + FrameMargins -> { { 8, 8 }, { 13, 13 } }, + Spacings -> { 0, 1.5 } +]; + +notebookSettingsPanel // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*personaSettingsPanel*) +personaSettingsPanel // beginDefinition; + +personaSettingsPanel[ ] := + DynamicModule[ + { display = ProgressIndicator[ Appearance -> "Percolate" ] }, + Dynamic[ display ], + Initialization :> (display = CreatePersonaManagerPanel[ ]), + SynchronousInitialization -> False, + UnsavedVariables :> { display } + ]; + +personaSettingsPanel // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*toolSettingsPanel*) +toolSettingsPanel // beginDefinition; + +toolSettingsPanel[ ] := + DynamicModule[ + { display = ProgressIndicator[ Appearance -> "Percolate" ] }, + Dynamic[ display ], + Initialization :> (display = CreateLLMToolManagerPanel[ ]), + SynchronousInitialization -> False, + UnsavedVariables :> { display } + ]; + +toolSettingsPanel // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*makeFrontEndAndNotebookSettingsContent*) +makeFrontEndAndNotebookSettingsContent // beginDefinition; + +makeFrontEndAndNotebookSettingsContent[ + targetObj : _FrontEndObject | $FrontEndSession | _NotebookObject +] := Module[{ + personas = GetPersonasAssociation[], + defaultPersonaPopupItems, + setModelPopupItems, + modelPopupItems +}, + defaultPersonaPopupItems = KeyValueMap[ + {persona, personaSettings} |-> ( + persona -> Row[{ + resizeMenuIcon[ + getPersonaMenuIcon[personaSettings, "Full"] + ], + personaDisplayName[persona, personaSettings] + }, Spacer[1]] + ), + personas + ]; + + (*----------------------------*) + (* Compute the models to show *) + (*----------------------------*) + + setModelPopupItems[] := ( + modelPopupItems = KeyValueMap[ + {modelName, settings} |-> ( + modelName -> Row[{ + getModelMenuIcon[settings, "Full"], + modelDisplayName[modelName] + }, Spacer[1]] + ), + Association[#Name -> # & /@ getServiceModelList["OpenAI"]] + ]; + ); + + (* Initial value. Called again if 'show snapshot models' changes. *) + setModelPopupItems[]; + + (*---------------------------------*) + (* Return the toolbar menu content *) + (*---------------------------------*) + + Grid[ + { + {Row[{ + tr["Default Persona:"], + PopupMenu[ + Dynamic[ + currentChatSettings[ + targetObj, + "LLMEvaluator" + ], + Function[{newValue}, + CurrentValue[ + targetObj, + {TaggingRules, "ChatNotebookSettings", "LLMEvaluator"} + ] = newValue + ] + ], + defaultPersonaPopupItems + ] + }, Spacer[3]]}, + {Row[{ + tr["Default Model:"], + (* Note: Dynamic[PopupMenu[..]] so that changing the + 'show snapshot models' option updates the popup. *) + Dynamic @ PopupMenu[ + Dynamic[ + currentChatSettings[ + targetObj, + "Model" + ], + Function[{newValue}, + CurrentValue[ + targetObj, + {TaggingRules, "ChatNotebookSettings", "Model"} + ] = newValue + ] + ], + modelPopupItems, + (* This is shown if the user selects a snapshot model, + and then unchecks the 'show snapshot models' option. *) + Dynamic[ + Style[ + With[{ + modelName = currentChatSettings[targetObj, "Model"] + }, { + settings = standardizeModelData[modelName] + }, + Row[{ + getModelMenuIcon[settings, "Full"], + modelDisplayName[modelName] + }, Spacer[1]] + ], + Italic + ] + ] + ] + }, Spacer[3]]}, + {Row[{ + tr["Default Tool Call Frequency:"], + makeToolCallFrequencySlider[ targetObj ] + }, Spacer[3]]}, + {Row[{ + tr["Default Temperature:"], + makeTemperatureSlider[ + Dynamic[ + currentChatSettings[targetObj, "Temperature"], + newValue |-> ( + CurrentValue[ + targetObj, + {TaggingRules, "ChatNotebookSettings", "Temperature"} + ] = newValue; + ) + ] + ] + }, Spacer[3]]}, + + If[ TrueQ @ $useLLMServices, + Nothing, + {Row[{ + tr["Chat Completion URL:"], + makeOpenAIAPICompletionURLForm[ + Dynamic[ + currentChatSettings[targetObj, "OpenAIAPICompletionURL"], + newValue |-> ( + CurrentValue[ + targetObj, + {TaggingRules, "ChatNotebookSettings", "OpenAIAPICompletionURL"} + ] = newValue; + ) + ] + ] + }, Spacer[3]]}], + { + labeledCheckbox[ + Dynamic[ + showSnapshotModelsQ[], + newValue |-> ( + CurrentValue[$FrontEnd, { + PrivateFrontEndOptions, + "InterfaceSettings", + "ChatNotebooks", + "ShowSnapshotModels" + }] = newValue; + + setModelPopupItems[]; + ) + ], + Row[{ + "Show temporary snapshot LLM models", + Spacer[3], + Tooltip[ + chatbookIcon["InformationTooltip", False], +"If enabled, temporary snapshot models will be included in the model selection menus. +\nSnapshot models are models that are frozen at a particular date, will not be +continuously updated, and have an expected discontinuation date." + ] + }] + ] + }, + { + makeAutomaticResultAnalysisCheckbox[targetObj] + } + }, + Alignment -> {Left, Baseline}, + Spacings -> {0, 0.7} + ] +]; + +makeFrontEndAndNotebookSettingsContent // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*makeOpenAIAPICompletionURLForm*) +(* cSpell: ignore AIAPI *) +makeOpenAIAPICompletionURLForm // beginDefinition; + +makeOpenAIAPICompletionURLForm[ value_ ] := Pane @ InputField[ + value, + String, + ImageSize -> { 240, Automatic }, + BaseStyle -> { FontSize -> 12 } +]; + +makeOpenAIAPICompletionURLForm // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Section::Closed:: *) +(*UI Elements*) + +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*$resetButton*) +$resetButton = + Module[ { icon, label }, + icon = Style[ + Dynamic @ RawBoxes @ FEPrivate`FrontEndResource[ "FEBitmaps", "SyntaxColorResetIcon" ][ + RGBColor[ 0.3921, 0.3921, 0.3921 ] + ], + GraphicsBoxOptions -> { BaselinePosition -> Scaled[ 0.1 ] } + ]; + + label = Grid[ + { { icon, Dynamic @ FEPrivate`FrontEndResource[ "PreferencesDialog", "ResetAllSettingsText" ] } }, + Alignment -> { Automatic, Baseline } + ]; + + Button[ + label, + + FrontEndExecute @ FrontEnd`RemoveOptions[ + $FrontEnd, + { System`LLMEvaluator, { TaggingRules, "ChatNotebookSettings" } } + ]; + + CurrentValue[ $FrontEnd, { PrivateFrontEndOptions, "InterfaceSettings", "ChatNotebooks" } ] = Inherited + , + BaseStyle -> { + FontFamily -> Dynamic @ FrontEnd`CurrentValue[ "ControlsFontFamily" ], + FontSize -> Dynamic @ FrontEnd`CurrentValue[ "ControlsFontSize" ], + FontColor -> Black + }, + ImageSize -> Automatic + ] + ]; + +(* ::**************************************************************************************************************:: *) +(* ::Section::Closed:: *) +(*Navigation*) + +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*openPreferencesPage*) +openPreferencesPage // beginDefinition; + +openPreferencesPage[ page: $$preferencesPage ] := ( + CurrentValue[ $FrontEnd, { "PreferencesSettings", "Page" } ] = "AI"; + CurrentValue[ $FrontEnd, { PrivateFrontEndOptions, "InterfaceSettings", "Chatbook", "PreferencesTab" } ] = page; + FrontEndTokenExecute[ "PreferencesDialog" ] +); + +openPreferencesPage // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Section::Closed:: *) +(*Package Footer*) +If[ Wolfram`ChatbookInternal`$BuildingMX, + Null; +]; + +End[ ]; +EndPackage[ ]; diff --git a/Source/Chatbook/UI.wl b/Source/Chatbook/UI.wl index c9cf0ffa..49a1b151 100644 --- a/Source/Chatbook/UI.wl +++ b/Source/Chatbook/UI.wl @@ -22,30 +22,39 @@ GeneralUtilities`SetUsage[CreateToolbarContent, " CreateToolbarContent[] is called by the NotebookToolbar to generate the content of the 'Notebook AI Settings' attached menu. "] -`getPersonaIcon; -`getPersonaMenuIcon; -`personaDisplayName; -`resizeMenuIcon; -`serviceIcon; - +HoldComplete[ + `getPersonaIcon; + `getPersonaMenuIcon; + `personaDisplayName; + `resizeMenuIcon; + `serviceIcon; + `tr; + `getModelMenuIcon; + `makeToolCallFrequencySlider; + `makeTemperatureSlider; + `labeledCheckbox; + `showSnapshotModelsQ; + `makeAutomaticResultAnalysisCheckbox; +]; Begin["`Private`"] -Needs[ "Wolfram`Chatbook`" ]; -Needs[ "Wolfram`Chatbook`Actions`" ]; -Needs[ "Wolfram`Chatbook`Common`" ]; -Needs[ "Wolfram`Chatbook`Dynamics`" ]; -Needs[ "Wolfram`Chatbook`Errors`" ]; -Needs[ "Wolfram`Chatbook`ErrorUtils`" ]; -Needs[ "Wolfram`Chatbook`FrontEnd`" ]; -Needs[ "Wolfram`Chatbook`Menus`" ]; -Needs[ "Wolfram`Chatbook`Models`" ]; -Needs[ "Wolfram`Chatbook`Personas`" ]; -Needs[ "Wolfram`Chatbook`PreferencesUtils`" ]; -Needs[ "Wolfram`Chatbook`Serialization`" ]; -Needs[ "Wolfram`Chatbook`Services`" ]; -Needs[ "Wolfram`Chatbook`Settings`" ]; -Needs[ "Wolfram`Chatbook`Utils`" ]; +Needs[ "Wolfram`Chatbook`" ]; +Needs[ "Wolfram`Chatbook`Actions`" ]; +Needs[ "Wolfram`Chatbook`Common`" ]; +Needs[ "Wolfram`Chatbook`Dynamics`" ]; +Needs[ "Wolfram`Chatbook`Errors`" ]; +Needs[ "Wolfram`Chatbook`ErrorUtils`" ]; +Needs[ "Wolfram`Chatbook`FrontEnd`" ]; +Needs[ "Wolfram`Chatbook`Menus`" ]; +Needs[ "Wolfram`Chatbook`Models`" ]; +Needs[ "Wolfram`Chatbook`Personas`" ]; +Needs[ "Wolfram`Chatbook`PreferencesContent`" ]; +Needs[ "Wolfram`Chatbook`PreferencesUtils`" ]; +Needs[ "Wolfram`Chatbook`Serialization`" ]; +Needs[ "Wolfram`Chatbook`Services`" ]; +Needs[ "Wolfram`Chatbook`Settings`" ]; +Needs[ "Wolfram`Chatbook`Utils`" ]; (* ::**************************************************************************************************************:: *) (* ::Section::Closed:: *) @@ -165,91 +174,7 @@ $cloudChatBanner := PaneSelector[ (* ::**************************************************************************************************************:: *) (* ::Section::Closed:: *) (*Preferences Panel*) -CreatePreferencesContent[] := Module[{ - personas = GetPersonasAssociation[], - chatbookSettings, - llmEvaluatorNamesSettings, - services, - grid -}, - - llmEvaluatorNamesSettings = Grid[ - Prepend[ - KeyValueMap[ - {persona, personaSettings} |-> { - resizeMenuIcon @ getPersonaMenuIcon[personaSettings, "Full"], - personaDisplayName[persona, personaSettings], - Replace[Lookup[personaSettings, "Description", None], { - None | _?MissingQ -> "", - desc_?StringQ :> desc, - other_ :> ( - ChatbookWarning[ - "Unexpected non-String persona `` description: ``", - InputForm[persona], - InputForm[other] - ]; - other - ) - }] - }, - personas - ], - {"", "Name", "Description"} - ], - Background -> {None, {1 -> GrayLevel[0.95]}}, - Dividers -> {False, {False, {1 -> True, 2 -> True}}}, - Alignment -> {Left, Center} - ]; - - chatbookSettings = makeFrontEndAndNotebookSettingsContent[$FrontEnd]; - - (* services = Grid[{ - {"" , "Name" , "State" }, - {chatbookIcon["OpenAILogo", False] , "OpenAI" , "" }, - {"" , "Bard" , Style["Coming soon", Italic] }, - {"" , "Claude" , Style["Coming soon", Italic] } - }, - Background -> {None, {1 -> GrayLevel[0.95]}}, - Dividers -> {False, {False, {1 -> True, 2 -> True}}}, - Alignment -> {Left, Center} - ]; *) - - (*-----------------------------------------*) - (* Return the complete settings expression *) - (*-----------------------------------------*) - - PreferencesPane[ - { - PreferencesSection[ - Style[tr["Chat Notebook Interface"], "subsectionText"], - chatbookSettings - ], - PreferencesSection[ - Style[tr["Installed Personas"], "subsectionText"], - llmEvaluatorNamesSettings - ] - (* PreferencesSection[ - Style[tr["LLM Service Providers"], "subsectionText"], - services - ] *) - }, - PreferencesResetButton[ - FrontEndExecute @ FrontEnd`RemoveOptions[$FrontEnd, { - System`LLMEvaluator, - {TaggingRules, "ChatNotebookSettings"} - }]; - - CurrentValue[ - $FrontEnd, - { - PrivateFrontEndOptions, - "InterfaceSettings", - "ChatNotebooks" - } - ] = Inherited; - ] - ] -] +CreatePreferencesContent[ ] := trackedDynamic[ createPreferencesContent[ ], { "Preferences" } ]; (* ::**************************************************************************************************************:: *) (* ::Section::Closed:: *) @@ -382,7 +307,7 @@ makeEnableAIChatFeaturesLabel[enabled_?BooleanQ] := SetFallthroughError[makeAutomaticResultAnalysisCheckbox] makeAutomaticResultAnalysisCheckbox[ - target : $FrontEnd | $FrontEndSession | _NotebookObject + target : _FrontEndObject | $FrontEndSession | _NotebookObject ] := With[{ setterFunction = ConfirmReplace[target, { $FrontEnd | $FrontEndSession :> ( @@ -580,193 +505,10 @@ makeTemperatureSlider[ BaseStyle -> { FontSize -> 12 } ] -(* cSpell: ignore AIAPI *) -makeOpenAIAPICompletionURLForm[value_]:= Pane[ - InputField[value, - String, - ImageSize -> {240, Automatic}, - BaseStyle -> {FontSize -> 12}] -] - (*=========================================*) (* Common preferences content construction *) (*=========================================*) -SetFallthroughError[makeFrontEndAndNotebookSettingsContent] - -makeFrontEndAndNotebookSettingsContent[ - targetObj : _FrontEndObject | $FrontEndSession | _NotebookObject -] := Module[{ - personas = GetPersonasAssociation[], - defaultPersonaPopupItems, - setModelPopupItems, - modelPopupItems -}, - defaultPersonaPopupItems = KeyValueMap[ - {persona, personaSettings} |-> ( - persona -> Row[{ - resizeMenuIcon[ - getPersonaMenuIcon[personaSettings, "Full"] - ], - personaDisplayName[persona, personaSettings] - }, Spacer[1]] - ), - personas - ]; - - (*----------------------------*) - (* Compute the models to show *) - (*----------------------------*) - - setModelPopupItems[] := ( - modelPopupItems = KeyValueMap[ - {modelName, settings} |-> ( - modelName -> Row[{ - getModelMenuIcon[settings, "Full"], - modelDisplayName[modelName] - }, Spacer[1]] - ), - getModelsMenuItems[] - ]; - ); - - (* Initial value. Called again if 'show snapshot models' changes. *) - setModelPopupItems[]; - - (*---------------------------------*) - (* Return the toolbar menu content *) - (*---------------------------------*) - - Grid[ - { - {Row[{ - tr["Default Persona:"], - PopupMenu[ - Dynamic[ - currentChatSettings[ - targetObj, - "LLMEvaluator" - ], - Function[{newValue}, - CurrentValue[ - targetObj, - {TaggingRules, "ChatNotebookSettings", "LLMEvaluator"} - ] = newValue - ] - ], - defaultPersonaPopupItems - ] - }, Spacer[3]]}, - {Row[{ - tr["Default Model:"], - (* Note: Dynamic[PopupMenu[..]] so that changing the - 'show snapshot models' option updates the popup. *) - Dynamic @ PopupMenu[ - Dynamic[ - currentChatSettings[ - targetObj, - "Model" - ], - Function[{newValue}, - CurrentValue[ - targetObj, - {TaggingRules, "ChatNotebookSettings", "Model"} - ] = newValue - ] - ], - modelPopupItems, - (* This is shown if the user selects a snapshot model, - and then unchecks the 'show snapshot models' option. *) - Dynamic[ - Style[ - With[{ - modelName = currentChatSettings[targetObj, "Model"] - }, { - settings = standardizeModelData[modelName] - }, - Row[{ - getModelMenuIcon[settings, "Full"], - modelDisplayName[modelName] - }, Spacer[1]] - ], - Italic - ] - ] - ] - }, Spacer[3]]}, - {Row[{ - tr["Default Tool Call Frequency:"], - makeToolCallFrequencySlider[ targetObj ] - }, Spacer[3]]}, - {Row[{ - tr["Default Temperature:"], - makeTemperatureSlider[ - Dynamic[ - currentChatSettings[targetObj, "Temperature"], - newValue |-> ( - CurrentValue[ - targetObj, - {TaggingRules, "ChatNotebookSettings", "Temperature"} - ] = newValue; - ) - ] - ] - }, Spacer[3]]}, - - If[ TrueQ @ $useLLMServices, - Nothing, - {Row[{ - tr["Chat Completion URL:"], - makeOpenAIAPICompletionURLForm[ - Dynamic[ - currentChatSettings[targetObj, "OpenAIAPICompletionURL"], - newValue |-> ( - CurrentValue[ - targetObj, - {TaggingRules, "ChatNotebookSettings", "OpenAIAPICompletionURL"} - ] = newValue; - ) - ] - ] - }, Spacer[3]]}], - { - labeledCheckbox[ - Dynamic[ - showSnapshotModelsQ[], - newValue |-> ( - CurrentValue[$FrontEnd, { - PrivateFrontEndOptions, - "InterfaceSettings", - "ChatNotebooks", - "ShowSnapshotModels" - }] = newValue; - - setModelPopupItems[]; - ) - ], - Row[{ - "Show temporary snapshot LLM models", - Spacer[3], - Tooltip[ - chatbookIcon["InformationTooltip", False], -"If enabled, temporary snapshot models will be included in the model selection menus. -\nSnapshot models are models that are frozen at a particular date, will not be -continuously updated, and have an expected discontinuation date." - ] - }] - ] - }, - { - makeAutomaticResultAnalysisCheckbox[targetObj] - } - }, - Alignment -> {Left, Baseline}, - Spacings -> {0, 0.7} - ] -] - -(*======================================*) - showSnapshotModelsQ[] := TrueQ @ CurrentValue[$FrontEnd, { PrivateFrontEndOptions, From ac2f1001f83da14c3e915329b8dc74c8b494ce3c Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Thu, 7 Dec 2023 08:01:19 -0500 Subject: [PATCH 10/50] Bugfix: avoid saving invalid values into preferences --- Source/Chatbook/PersonaManager.wl | 19 ++++++++++++++----- 1 file changed, 14 insertions(+), 5 deletions(-) diff --git a/Source/Chatbook/PersonaManager.wl b/Source/Chatbook/PersonaManager.wl index e3f29111..1ad97d71 100644 --- a/Source/Chatbook/PersonaManager.wl +++ b/Source/Chatbook/PersonaManager.wl @@ -146,11 +146,20 @@ CreatePersonaManagerPanel[ ] := DynamicModule[{favorites, delimColor}, delimColor = CurrentValue[{StyleDefinitions, "DialogDelimiter", CellFrameColor}]; GetPersonaData[]; (* sets $CachedPersonaData *) (* make sure there are no unexpected extra personas *) - CurrentValue[$FrontEnd, {PrivateFrontEndOptions, "InterfaceSettings", "Chatbook", "VisiblePersonas"}] = - Intersection[ - CurrentValue[$FrontEnd, {PrivateFrontEndOptions, "InterfaceSettings", "Chatbook", "VisiblePersonas"}], - Keys[$CachedPersonaData]]), - Deinitialization :> (CurrentValue[$FrontEnd, {PrivateFrontEndOptions, "InterfaceSettings", "Chatbook", "PersonaFavorites"}] = favorites) + Enclose[ + CurrentValue[$FrontEnd, {PrivateFrontEndOptions, "InterfaceSettings", "Chatbook", "VisiblePersonas"}] = + ConfirmBy[ + Intersection[ + CurrentValue[$FrontEnd, {PrivateFrontEndOptions, "InterfaceSettings", "Chatbook", "VisiblePersonas"}], + Keys[$CachedPersonaData] + ], + ListQ + ] + ] + ), + Deinitialization :> If[ MatchQ[ favorites, { ___String } ], + CurrentValue[$FrontEnd, {PrivateFrontEndOptions, "InterfaceSettings", "Chatbook","PersonaFavorites"}] = favorites + ] ]; CreatePersonaManagerPanel // endDefinition; From 5ae7a9c135ea3beeb024f116563ea37a0d55c17e Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Thu, 7 Dec 2023 08:01:43 -0500 Subject: [PATCH 11/50] Bugfix: update `toolsEnabledQ` to handle new model format --- Source/Chatbook/SendChat.wl | 1 + 1 file changed, 1 insertion(+) diff --git a/Source/Chatbook/SendChat.wl b/Source/Chatbook/SendChat.wl index 85402828..d61a07cf 100644 --- a/Source/Chatbook/SendChat.wl +++ b/Source/Chatbook/SendChat.wl @@ -1445,6 +1445,7 @@ getNamedLLMEvaluator // endDefinition; toolsEnabledQ[ KeyValuePattern[ "ToolsEnabled" -> enabled: True|False ] ] := enabled; toolsEnabledQ[ KeyValuePattern[ "ToolCallFrequency" -> freq: (_Integer|_Real)? NonPositive ] ] := False; toolsEnabledQ[ KeyValuePattern[ "Model" -> model_ ] ] := toolsEnabledQ @ toModelName @ model; +toolsEnabledQ[ model: KeyValuePattern @ { "Service" -> _, "Name" -> _ } ] := toolsEnabledQ @ toModelName @ model; toolsEnabledQ[ "chat-bison-001" ] := False; toolsEnabledQ[ model_String ] := ! TrueQ @ StringContainsQ[ model, "gpt-3", IgnoreCase -> True ]; toolsEnabledQ[ ___ ] := False; From a9bd504eee0b9c232a4dceb36ebbd1f03291fcc9 Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Thu, 7 Dec 2023 09:54:42 -0500 Subject: [PATCH 12/50] Use slightly different display for tool manager when showing in preferences --- Source/Chatbook/ToolManager.wl | 84 +++++++++++++++++++++++----------- 1 file changed, 58 insertions(+), 26 deletions(-) diff --git a/Source/Chatbook/ToolManager.wl b/Source/Chatbook/ToolManager.wl index d2e5f0a1..dd5b7b37 100644 --- a/Source/Chatbook/ToolManager.wl +++ b/Source/Chatbook/ToolManager.wl @@ -50,17 +50,22 @@ CreateLLMToolManagerDialog // endDefinition; (*CreateLLMToolManagerPanel*) CreateLLMToolManagerPanel // beginDefinition; -CreateLLMToolManagerPanel[ ] := catchMine @ trackedDynamic[ - CreateLLMToolManagerPanel[ getFullToolList[ ], getFullPersonaList[ ] ], - { "Tools", "Personas" } -]; +CreateLLMToolManagerPanel[ ] := catchMine @ + With[ { inDialog = $inDialog }, + trackedDynamic[ + Block[ { $inDialog = inDialog }, + CreateLLMToolManagerPanel[ getFullToolList[ ], getFullPersonaList[ ] ] + ], + { "Tools", "Personas" } + ] + ]; CreateLLMToolManagerPanel[ tools0_List, personas_List ] := catchMine @ cvExpand @ Module[ { globalTools, personaTools, personaToolNames, personaToolLookup, tools, preppedPersonas, preppedTools, personaNames, personaDisplayNames, - toolNames, toolDefaultPersonas, gridOpts + toolNames, toolDefaultPersonas, gridOpts, marginL, marginH, margins }, globalTools = toolName @ tools0; @@ -95,8 +100,8 @@ CreateLLMToolManagerPanel[ tools0_List, personas_List ] := { sH = 0, sV = 0, - w = 167, - h = 180, + w = If[ TrueQ @ $inDialog, 167, UpTo[ 230 ] ], + h = If[ TrueQ @ $inDialog, 180, Automatic ], row = None, column = None, scopeMode = $FrontEnd &, @@ -128,12 +133,19 @@ CreateLLMToolManagerPanel[ tools0_List, personas_List ] := ] ]; + marginL = If[ TrueQ @ $inDialog, Automatic, 5 ]; + marginH = { marginL, Automatic }; + margins = { marginH, Automatic }; + DynamicWrapper[ Grid[ { (* ----- Install Tools ----- *) - dialogHeader[ "Add & Manage LLM Tools" ], - dialogSubHeader[ "Install Tools" ], + If[ TrueQ @ $inDialog, dialogHeader[ "Add & Manage LLM Tools" ], Nothing ], + dialogSubHeader[ + "Install Tools", + margins + ], dialogBody[ Grid @ { { @@ -153,13 +165,14 @@ CreateLLMToolManagerPanel[ tools0_List, personas_List ] := Method -> "Queued" ] } - } + }, + margins ], (* ----- Configure and Enable Tools ----- *) - dialogSubHeader[ "Manage and Enable Tools" ], + dialogSubHeader[ "Manage and Enable Tools", margins ], dialogBody[ Grid @ { { @@ -168,7 +181,7 @@ CreateLLMToolManagerPanel[ tools0_List, personas_List ] := Dynamic @ catchAlways @ toolModelWarning @ scopeMode[ ] } }, - { Automatic, { 5, Automatic } } + { marginH, { 5, Automatic } } ], dialogBody[ EventHandler[ @@ -176,12 +189,15 @@ CreateLLMToolManagerPanel[ tools0_List, personas_List ] := { Append[ Map[ - Function @ EventHandler[ - Pane[ #, FrameMargins -> { { 0, 0 }, { 2, 2 } } ], - { "MouseEntered" :> FEPrivate`Set[ { row, column }, { None, None } ] } + Function @ Item[ + EventHandler[ + Pane[ #, FrameMargins -> { { 0, 0 }, { 2, 2 } } ], + { "MouseEntered" :> FEPrivate`Set[ { row, column }, { None, None } ] } + ], + Background -> GrayLevel[ 0.898 ] ], { - "Tool", + Row @ { Spacer[ 4 ], "Tool" }, Row @ { Spacer[ 4 ], "Enabled for\[VeryThinSpace]:", @@ -229,7 +245,7 @@ CreateLLMToolManagerPanel[ tools0_List, personas_List ] := (* Checkbox grid: *) linkedPane[ Grid[ - Table[ + (*fitLastColumn @*) Table[ If[ And[ StringQ @ personaToolLookup @ tools[[ i, "CanonicalName" ]], UnsameQ[ @@ -286,7 +302,8 @@ CreateLLMToolManagerPanel[ tools0_List, personas_List ] := ] ], Dynamic @ { sH, sV }, - Scrollbars -> { Automatic, False } + Scrollbars -> { Automatic, False }, + AppearanceElements -> If[ TrueQ @ $inDialog, Automatic, None ] ], (* All/None and clear column: *) @@ -317,18 +334,19 @@ CreateLLMToolManagerPanel[ tools0_List, personas_List ] := ] } }, - Alignment -> { Left, Top }, - BaseStyle -> $baseStyle, - ItemSize -> { 0, 0 }, - Spacings -> { 0, 0 }, - Dividers -> { + Alignment -> { Left, Top }, + Background -> White, + BaseStyle -> $baseStyle, + ItemSize -> { 0, 0 }, + Spacings -> { 0, 0 }, + Dividers -> { { False, $dividerCol, $dividerCol, { False } }, { False, False , $dividerCol, { False } } } ], { "MouseExited" :> FEPrivate`Set[ { row, column }, { None, None } ] }, PassEventsDown -> True - ], { { Automatic, 0 }, Automatic } ], + ], { { marginL, 0 }, Automatic } ], If[ TrueQ @ $inDialog, { @@ -438,6 +456,20 @@ CreateLLMToolManagerPanel[ tools0_List, personas_List ] := CreateLLMToolManagerPanel // endDefinition; +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*fitLastColumn*) +fitLastColumn // beginDefinition; + +fitLastColumn[ grid_? MatrixQ ] := + MapAt[ + Item[ #, ItemSize -> { Fit, Automatic }, Alignment -> { Left, Automatic } ] &, + grid, + { All, -1 } + ]; + +fitLastColumn // endDefinition; + (* ::**************************************************************************************************************:: *) (* ::Subsection::Closed:: *) (*addPersonaSource*) @@ -589,8 +621,8 @@ toolModelWarning0[ scope_, model_String ] := Enclose[ Grid[ { { Spacer[ 5 ], - Style[ "\[WarningSign]", FontWeight -> Bold, FontColor -> Darker @ Orange, FontSize -> 18 ], - message + Style[ "\[WarningSign]", FontWeight -> Bold, FontColor -> Gray, FontSize -> 18 ], + Style[ message, FontColor -> Gray, FontSlant -> Italic ] } }, Alignment -> { Left, Top } ] From 3956c3402126c6bbefb543f1cbafb65851fa1c31 Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Thu, 7 Dec 2023 09:55:29 -0500 Subject: [PATCH 13/50] Bugfix: use consistent naming in `PrivateFrontEndOptions` --- Source/Chatbook/PreferencesContent.wl | 2 +- Source/Chatbook/UI.wl | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/Source/Chatbook/PreferencesContent.wl b/Source/Chatbook/PreferencesContent.wl index 48c7b27c..582249e2 100644 --- a/Source/Chatbook/PreferencesContent.wl +++ b/Source/Chatbook/PreferencesContent.wl @@ -292,7 +292,7 @@ makeFrontEndAndNotebookSettingsContent[ CurrentValue[$FrontEnd, { PrivateFrontEndOptions, "InterfaceSettings", - "ChatNotebooks", + "Chatbook", "ShowSnapshotModels" }] = newValue; diff --git a/Source/Chatbook/UI.wl b/Source/Chatbook/UI.wl index 49a1b151..bee3491a 100644 --- a/Source/Chatbook/UI.wl +++ b/Source/Chatbook/UI.wl @@ -513,7 +513,7 @@ showSnapshotModelsQ[] := TrueQ @ CurrentValue[$FrontEnd, { PrivateFrontEndOptions, "InterfaceSettings", - "ChatNotebooks", + "Chatbook", "ShowSnapshotModels" }] From 9e959ff94428424e83e57b066cfbdf69a013cbfd Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Thu, 7 Dec 2023 09:56:02 -0500 Subject: [PATCH 14/50] Bugfix: persona checkboxes weren't responding to programmatic changes --- Source/Chatbook/PersonaManager.wl | 28 +++++++++++++++++----------- 1 file changed, 17 insertions(+), 11 deletions(-) diff --git a/Source/Chatbook/PersonaManager.wl b/Source/Chatbook/PersonaManager.wl index 1ad97d71..3f1796f6 100644 --- a/Source/Chatbook/PersonaManager.wl +++ b/Source/Chatbook/PersonaManager.wl @@ -266,18 +266,24 @@ formatPacletLink[ origin_String, url_, pacletName_ ] := formatPacletLink // endDefinition; addRemovePersonaListingCheckbox // beginDefinition; + addRemovePersonaListingCheckbox[ name_String ] := - DynamicModule[{val}, - Checkbox[ - Dynamic[val, - Function[ - val = #; - CurrentValue[$FrontEnd, {PrivateFrontEndOptions, "InterfaceSettings", "Chatbook", "VisiblePersonas"}] = - If[#, - Union[Replace[CurrentValue[$FrontEnd, {PrivateFrontEndOptions, "InterfaceSettings", "Chatbook", "VisiblePersonas"}], Except[{___String}] :> {}], {name}] - , - DeleteCases[CurrentValue[$FrontEnd, {PrivateFrontEndOptions, "InterfaceSettings", "Chatbook", "VisiblePersonas"}], name]]]]], - Initialization :> (val = MemberQ[CurrentValue[$FrontEnd, {PrivateFrontEndOptions, "InterfaceSettings", "Chatbook", "VisiblePersonas"}], name])]; + With[ + { + path = { PrivateFrontEndOptions, "InterfaceSettings", "Chatbook", "VisiblePersonas" }, + core = $corePersonaNames + }, + Checkbox @ Dynamic[ + MemberQ[ CurrentValue[ $FrontEnd, path, core ], name ], + Function[ + CurrentValue[ $FrontEnd, path ] = + With[ { current = Replace[ CurrentValue[ $FrontEnd, path ], Except[ { ___String } ] :> core ] }, + If[ #, Union[ current, { name } ], Complement[ current, { name } ] ] + ] + ] + ] + ]; + addRemovePersonaListingCheckbox // endDefinition; uninstallButton // beginDefinition; From e288e77115ab43b5fe13cd48f1ec917d2646a932 Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Thu, 7 Dec 2023 09:57:13 -0500 Subject: [PATCH 15/50] Reset button has custom behavior depending on which tab is being viewed --- Source/Chatbook/PreferencesContent.wl | 62 +++++++++++++++++++-------- 1 file changed, 45 insertions(+), 17 deletions(-) diff --git a/Source/Chatbook/PreferencesContent.wl b/Source/Chatbook/PreferencesContent.wl index 582249e2..42352895 100644 --- a/Source/Chatbook/PreferencesContent.wl +++ b/Source/Chatbook/PreferencesContent.wl @@ -9,18 +9,18 @@ HoldComplete[ Begin[ "`Private`" ]; -Needs[ "Wolfram`Chatbook`" ]; -Needs[ "Wolfram`Chatbook`Common`" ]; -Needs[ "Wolfram`Chatbook`Personas`" ]; -Needs[ "Wolfram`Chatbook`UI`" ]; -Needs[ "Wolfram`Chatbook`Errors`" ]; +Needs[ "Wolfram`Chatbook`" ]; +Needs[ "Wolfram`Chatbook`Common`" ]; +Needs[ "Wolfram`Chatbook`Dynamics`" ]; +Needs[ "Wolfram`Chatbook`Errors`" ]; +Needs[ "Wolfram`Chatbook`Models`" ]; +Needs[ "Wolfram`Chatbook`PersonaManager`" ]; +Needs[ "Wolfram`Chatbook`Personas`" ]; Needs[ "Wolfram`Chatbook`PreferencesUtils`" ]; -Needs[ "Wolfram`Chatbook`Settings`" ]; -Needs[ "Wolfram`Chatbook`Models`" ]; -Needs[ "Wolfram`Chatbook`Services`" ]; -Needs[ "Wolfram`Chatbook`Dynamics`" ]; -Needs[ "Wolfram`Chatbook`ToolManager`" ]; -Needs[ "Wolfram`Chatbook`PersonaManager`" ]; +Needs[ "Wolfram`Chatbook`Services`" ]; +Needs[ "Wolfram`Chatbook`Settings`" ]; +Needs[ "Wolfram`Chatbook`ToolManager`" ]; +Needs[ "Wolfram`Chatbook`UI`" ]; (* ::**************************************************************************************************************:: *) (* ::Section::Closed:: *) @@ -361,22 +361,50 @@ $resetButton = Button[ label, - FrontEndExecute @ FrontEnd`RemoveOptions[ + Needs[ "Wolfram`Chatbook`" -> None ]; + resetChatPreferences @ CurrentValue[ $FrontEnd, - { System`LLMEvaluator, { TaggingRules, "ChatNotebookSettings" } } - ]; - - CurrentValue[ $FrontEnd, { PrivateFrontEndOptions, "InterfaceSettings", "ChatNotebooks" } ] = Inherited + { PrivateFrontEndOptions, "InterfaceSettings", "Chatbook", "PreferencesTab" } + ] , BaseStyle -> { FontFamily -> Dynamic @ FrontEnd`CurrentValue[ "ControlsFontFamily" ], FontSize -> Dynamic @ FrontEnd`CurrentValue[ "ControlsFontSize" ], FontColor -> Black }, - ImageSize -> Automatic + ImageSize -> Automatic, + Method -> "Queued" ] ]; +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*resetChatPreferences*) +resetChatPreferences // beginDefinition; + +resetChatPreferences[ "Notebooks" ] := + FrontEndExecute @ FrontEnd`RemoveOptions[ + $FrontEnd, + { System`LLMEvaluator, { TaggingRules, "ChatNotebookSettings" } } + ]; + +resetChatPreferences[ "Personas" ] := + With[ { path = Sequence[ PrivateFrontEndOptions, "InterfaceSettings", "Chatbook" ] }, + (* TODO: choice dialog to uninstall personas *) + resetChatPreferences[ "Notebooks" ]; + CurrentValue[ $FrontEnd, { path, "VisiblePersonas" } ] = $corePersonaNames; + CurrentValue[ $FrontEnd, { path, "PersonaFavorites" } ] = $corePersonaNames; + updateDynamics[ "Preferences" ]; + ]; + +resetChatPreferences[ "Tools" ] := ( + (* TODO: choice dialog to uninstall tools *) + resetChatPreferences[ "Notebooks" ]; + updateDynamics[ "Preferences" ]; +); + +resetChatPreferences // endDefinition; + (* ::**************************************************************************************************************:: *) (* ::Section::Closed:: *) (*Navigation*) From dc6d13071c65a0f3c1125154039171a15eb5289b Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Thu, 7 Dec 2023 10:59:05 -0500 Subject: [PATCH 16/50] Bugfix: ensure chatbook context is not on $ContextPath when building/formatting stylesheet --- Developer/StylesheetBuilder.wl | 34 ++++++++++++++++++---------------- Scripts/FormatFiles.wls | 8 +++++--- 2 files changed, 23 insertions(+), 19 deletions(-) diff --git a/Developer/StylesheetBuilder.wl b/Developer/StylesheetBuilder.wl index bda263a0..f9954595 100644 --- a/Developer/StylesheetBuilder.wl +++ b/Developer/StylesheetBuilder.wl @@ -569,22 +569,24 @@ $ChatbookStylesheet = Notebook[ BuildChatbookStylesheet[ ] := BuildChatbookStylesheet @ $styleSheetTarget; BuildChatbookStylesheet[ target_ ] := - Module[ { exported }, - exported = Export[ target, $ChatbookStylesheet, "NB" ]; - PacletInstall[ "Wolfram/PacletCICD" ]; - Needs[ "Wolfram`PacletCICD`" -> None ]; - SetOptions[ - ResourceFunction[ "SaveReadableNotebook" ], - "RealAccuracy" -> 10, - "ExcludedNotebookOptions" -> { - ExpressionUUID, - FrontEndVersion, - WindowMargins, - WindowSize - } - ]; - Wolfram`PacletCICD`FormatNotebooks @ exported; - exported + Block[ { $Context = "Global`", $ContextPath = { "System`", "Global`" } }, + Module[ { exported }, + exported = Export[ target, $ChatbookStylesheet, "NB" ]; + PacletInstall[ "Wolfram/PacletCICD" ]; + Needs[ "Wolfram`PacletCICD`" -> None ]; + SetOptions[ + ResourceFunction[ "SaveReadableNotebook" ], + "RealAccuracy" -> 10, + "ExcludedNotebookOptions" -> { + ExpressionUUID, + FrontEndVersion, + WindowMargins, + WindowSize + } + ]; + Wolfram`PacletCICD`FormatNotebooks @ exported; + exported + ] ]; diff --git a/Scripts/FormatFiles.wls b/Scripts/FormatFiles.wls index 6ff8f48d..d5624bd6 100644 --- a/Scripts/FormatFiles.wls +++ b/Scripts/FormatFiles.wls @@ -160,9 +160,11 @@ makeReadable[ file_, formatted_File ] := (* ::**************************************************************************************************************:: *) (* ::Section::Closed:: *) (*Run*) -If[ MemberQ[ $ScriptCommandLine, "--unformat" ], - makeUnreadable /@ getFiles[ ], - makeReadable /@ Echo[ getFiles[ ] ] +Block[ { $Context = "Global`", $ContextPath = { "System`", "Global`" } }, + If[ MemberQ[ $ScriptCommandLine, "--unformat" ], + makeUnreadable /@ getFiles[ ], + makeReadable /@ Echo[ getFiles[ ] ] + ] ] (* :!CodeAnalysis::EndBlock:: *) \ No newline at end of file From 287419a7ff7c527b03de43dfaf5b4c965df1acdb Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Thu, 7 Dec 2023 11:00:22 -0500 Subject: [PATCH 17/50] Rebuilt stylesheet --- FrontEnd/StyleSheets/Chatbook.nb | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/FrontEnd/StyleSheets/Chatbook.nb b/FrontEnd/StyleSheets/Chatbook.nb index fb0dff3a..08db8e93 100644 --- a/FrontEnd/StyleSheets/Chatbook.nb +++ b/FrontEnd/StyleSheets/Chatbook.nb @@ -760,7 +760,7 @@ Notebook[ Cell[ BoxData[ DynamicBox[ - ToBoxes[$IncludedCellWidget, StandardForm], + ToBoxes[Wolfram`Chatbook`$IncludedCellWidget, StandardForm], SingleEvaluation -> True ] ], @@ -1161,7 +1161,7 @@ Notebook[ ], Cell[ StyleData["ChatStyleSheetInformation"], - TaggingRules -> <|"StyleSheetVersion" -> "1.3.4.3910857306"|> + TaggingRules -> <|"StyleSheetVersion" -> "1.3.4.3910935567"|> ], Cell[ StyleData["Text"], From 79f9d63646838b79a17be0321bfa729fc60438c3 Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Thu, 7 Dec 2023 11:41:23 -0500 Subject: [PATCH 18/50] Improved service caching and a public function to invalidate cache --- Source/Chatbook/Main.wl | 1 + Source/Chatbook/Models.wl | 3 + Source/Chatbook/PreferencesContent.wl | 6 ++ Source/Chatbook/Services.wl | 122 +++++++++++++++++--------- Source/Chatbook/ToolManager.wl | 2 +- Source/Chatbook/UI.wl | 3 + 6 files changed, 96 insertions(+), 41 deletions(-) diff --git a/Source/Chatbook/Main.wl b/Source/Chatbook/Main.wl index 2a62801c..12d526b3 100644 --- a/Source/Chatbook/Main.wl +++ b/Source/Chatbook/Main.wl @@ -31,6 +31,7 @@ BeginPackage[ "Wolfram`Chatbook`" ]; `GetChatHistory; `GetExpressionURI; `GetExpressionURIs; +`InvalidateServiceCache; `MakeExpressionURI; `SetModel; `SetToolOptions; diff --git a/Source/Chatbook/Models.wl b/Source/Chatbook/Models.wl index ef80207c..0b8ba160 100644 --- a/Source/Chatbook/Models.wl +++ b/Source/Chatbook/Models.wl @@ -328,6 +328,9 @@ standardizeModelData[ service_String, model_ ] := (standardizeModelData[ service, model ] = <| "Service" -> service, as |>) /; AssociationQ @ as ]; +standardizeModelData[ KeyValuePattern[ "Service" -> service_String ], model_ ] := + standardizeModelData[ service, model ]; + standardizeModelData // endDefinition; (* ::**************************************************************************************************************:: *) diff --git a/Source/Chatbook/PreferencesContent.wl b/Source/Chatbook/PreferencesContent.wl index 42352895..3c23f516 100644 --- a/Source/Chatbook/PreferencesContent.wl +++ b/Source/Chatbook/PreferencesContent.wl @@ -403,6 +403,12 @@ resetChatPreferences[ "Tools" ] := ( updateDynamics[ "Preferences" ]; ); +resetChatPreferences[ "Services" ] := ( + (* TODO: choice dialog to clear service connections *) + resetChatPreferences[ "Notebooks" ]; + updateDynamics[ "Preferences" ]; +); + resetChatPreferences // endDefinition; (* ::**************************************************************************************************************:: *) diff --git a/Source/Chatbook/Services.wl b/Source/Chatbook/Services.wl index 675ae8fd..a953d621 100644 --- a/Source/Chatbook/Services.wl +++ b/Source/Chatbook/Services.wl @@ -10,6 +10,7 @@ HoldComplete[ `$servicesLoaded; `$useLLMServices; `getAvailableServiceNames; + `getAvailableServices; `getServiceModelList; `modelListCachedQ; ]; @@ -19,6 +20,7 @@ Begin[ "`Private`" ]; Needs[ "Wolfram`Chatbook`" ]; Needs[ "Wolfram`Chatbook`Common`" ]; Needs[ "Wolfram`Chatbook`Models`" ]; +Needs[ "Wolfram`Chatbook`UI`" ]; $ContextAliases[ "llm`" ] = "LLMServices`"; @@ -30,12 +32,20 @@ $modelListCache = <| |>; $modelSortOrder = { "Snapshot", "FineTuned", "DisplayName" }; $servicesLoaded = False; $useLLMServices := MatchQ[ $enableLLMServices, Automatic|True ] && TrueQ @ $llmServicesAvailable; +$serviceCache = None; $llmServicesAvailable := $llmServicesAvailable = ( PacletInstall[ "Wolfram/LLMFunctions" ]; PacletNewerQ[ PacletObject[ "Wolfram/LLMFunctions" ], "1.2.2" ] ); +(* ::**************************************************************************************************************:: *) +(* ::Section::Closed:: *) +(*InvalidateServiceCache*) +InvalidateServiceCache // beginDefinition; +InvalidateServiceCache[ ] := ($serviceCache = None; Null); +InvalidateServiceCache // endDefinition; + (* ::**************************************************************************************************************:: *) (* ::Section::Closed:: *) (*Available Services*) @@ -44,7 +54,7 @@ $llmServicesAvailable := $llmServicesAvailable = ( (* ::Subsection::Closed:: *) (*modelListCachedQ*) modelListCachedQ // beginDefinition; -modelListCachedQ[ service_String ] := ListQ @ Lookup[ $modelListCache, service ]; +modelListCachedQ[ service_String ] := ListQ @ $serviceCache[ service, "CachedModels" ]; modelListCachedQ // endDefinition; (* ::**************************************************************************************************************:: *) @@ -56,35 +66,32 @@ $availableServiceNames := getAvailableServiceNames[ ]; (* ::Subsection::Closed:: *) (*getAvailableServiceNames*) getAvailableServiceNames // beginDefinition; -getAvailableServiceNames[ ] := getAvailableServiceNames @ $useLLMServices; -getAvailableServiceNames[ False ] := Keys @ $fallBackServices; -getAvailableServiceNames[ True ] := getAvailableServiceNames0[ ]; +getAvailableServiceNames[ ] := getAvailableServiceNames @ $availableServices; +getAvailableServiceNames[ services_Association ] := Keys @ services; getAvailableServiceNames // endDefinition; - -getAvailableServiceNames0 // beginDefinition; - -getAvailableServiceNames0[ ] := ( - PacletInstall[ "Wolfram/LLMFunctions" ]; - Needs[ "LLMServices`" -> None ]; - getAvailableServiceNames0 @ llm`LLMServiceInformation @ llm`ChatSubmit -); - -getAvailableServiceNames0[ services_Association ] := - Keys @ services; - -getAvailableServiceNames0 // endDefinition; +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*getServiceInformation*) +getServiceInformation // beginDefinition; +getServiceInformation[ service_String ] := getServiceInformation[ service, $availableServices ]; +getServiceInformation[ service_String, services_Association ] := Lookup[ services, service, Missing[ "NotAvailable" ] ]; +getServiceInformation // endDefinition; (* ::**************************************************************************************************************:: *) (* ::Subsection::Closed:: *) (*getServiceModels*) getServiceModelList // beginDefinition; +getServiceModelList[ KeyValuePattern[ "Service" -> service_String ] ] := + getServiceModelList @ service; + getServiceModelList[ service_String ] := - Lookup[ - $modelListCache, - service, - getServiceModelList[ service, llm`LLMServiceInformation[ llm`ChatSubmit, service ] ] + With[ { models = $availableServices[ service, "CachedModels" ] }, + If[ ListQ @ models, + models, + getServiceModelList[ service, $availableServices[ service ] ] + ] ]; getServiceModelList[ service_String, info_Association ] := @@ -99,16 +106,32 @@ getServiceModelList[ "OpenAI", info_, models: { "gpt-4", "gpt-3.5-turbo-0613" } ]; getServiceModelList[ service_String, info_, models0_List ] := Enclose[ - Module[ { models, ordering, sorted }, + Module[ { models }, + models = ConfirmMatch[ preprocessModelList[ service, models0 ], { ___Association }, "Models" ]; + ConfirmAssert[ AssociationQ @ $serviceCache[ service ], "ServiceCache" ]; + $serviceCache[ service, "CachedModels" ] = models + ], + throwInternalFailure +]; + +getServiceModelList // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*preprocessModelList*) +preprocessModelList // beginDefinition; + +preprocessModelList[ service_, models0_List ] := Enclose[ + Module[ { models, ordering, sorted }, models = ConfirmMatch[ standardizeModelData[ service, models0 ], { ___Association }, "Models" ]; ordering = Lookup /@ ConfirmMatch[ $modelSortOrder, { __String }, "ModelSortOrder" ]; sorted = SortBy[ models, ordering ]; - $modelListCache[ service ] = sorted + sorted ], throwInternalFailure ]; -getServiceModelList // endDefinition; +preprocessModelList // endDefinition; (* ::**************************************************************************************************************:: *) (* ::Subsubsection::Closed:: *) @@ -139,6 +162,9 @@ getAvailableServices // endDefinition; getAvailableServices0 // beginDefinition; +getAvailableServices0[ ] := + With[ { services = $serviceCache }, services /; AssociationQ @ services ]; + getAvailableServices0[ ] := ( PacletInstall[ "Wolfram/LLMFunctions" ]; Needs[ "LLMServices`" -> None ]; @@ -146,38 +172,54 @@ getAvailableServices0[ ] := ( ); getAvailableServices0[ services0_Association? AssociationQ ] := Enclose[ - Catch @ Module[ { services, withServiceName, withModels }, + Catch @ Module[ { services, withServiceName, withIcon, preCached }, + + services = ConfirmMatch[ + Replace[ services0, <| |> :> $fallBackServices ], + _Association? (AllTrue[ AssociationQ ]), + "Services" + ]; - services = Replace[ services0, <| |> :> $fallBackServices ]; withServiceName = Association @ KeyValueMap[ #1 -> <| "Service" -> #1, #2 |> &, services ]; + withIcon = Association[ #, "Icon" -> serviceIcon @ # ] & /@ withServiceName; - withModels = Replace[ - withServiceName, - as: KeyValuePattern @ { "Service" -> service_String } :> - RuleCondition @ With[ { models = getServiceModelList @ service }, - If[ ListQ @ models, (* workaround for KeyValuePattern bug *) - <| as, "Models" -> standardizeModelData[ service, models ] |>, - as - ] - ], - { 1 } + preCached = ConfirmMatch[ + checkLiteralModelLists /@ withIcon, + _Association? (AllTrue[ AssociationQ ]), + "CacheCheck" ]; $servicesLoaded = True; - - getAvailableServices0[ services0 ] = withModels + $serviceCache = preCached ], - throwInternalFailure[ getAvailableServices0[ ], ## ] & + throwInternalFailure ]; getAvailableServices0 // endDefinition; +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*checkLiteralModelLists*) +checkLiteralModelLists // beginDefinition; + +checkLiteralModelLists[ service: KeyValuePattern[ "ModelList" -> models_List ] ] := + Association[ service, "CachedModels" -> preprocessModelList[ service, models ] ]; + +checkLiteralModelLists[ service: KeyValuePattern[ "ModelList" :> models: { (_String | KeyValuePattern @ { })... } ] ] := + Association[ service, "CachedModels" -> preprocessModelList[ service, models ] ]; + +checkLiteralModelLists[ service_Association ] := + service; + +checkLiteralModelLists // endDefinition; + (* ::**************************************************************************************************************:: *) (* ::Subsection::Closed:: *) (*$fallBackServices*) $fallBackServices = <| "OpenAI" -> <| - "ModelList" -> getOpenAIChatModels + "Icon" -> chatbookIcon[ "ServiceIconOpenAI" ], + "ModelList" :> getOpenAIChatModels[ ] |> |>; diff --git a/Source/Chatbook/ToolManager.wl b/Source/Chatbook/ToolManager.wl index dd5b7b37..2904dc3a 100644 --- a/Source/Chatbook/ToolManager.wl +++ b/Source/Chatbook/ToolManager.wl @@ -610,7 +610,7 @@ toolModelWarning[ scope_, enabled_, model_? toolsEnabledQ ] := ""; toolModelWarning[ scope_, enabled_, model_ ] := toolModelWarning0[ scope, model ]; toolModelWarning // endDefinition; - +(* FIXME: add a link to open the Notebooks preferences tab *) toolModelWarning0 // beginDefinition; toolModelWarning0[ scope_, model_String ] := Enclose[ diff --git a/Source/Chatbook/UI.wl b/Source/Chatbook/UI.wl index bee3491a..6becde36 100644 --- a/Source/Chatbook/UI.wl +++ b/Source/Chatbook/UI.wl @@ -1072,6 +1072,9 @@ serviceIcon[ _String, "OpenAI" ] := serviceIcon[ _, service_String ] := alignedMenuIcon[ Style[ $currentSelectionCheck, ShowContents -> False ], serviceIcon @ service ]; +serviceIcon[ KeyValuePattern @ { "Service" -> _String, "Icon" -> icon: Except[ "" ] } ] := + icon; + serviceIcon[ KeyValuePattern[ "Service" -> service_String ] ] := serviceIcon @ service; From 23d70891ba642b4f641aefc13acd95d37547aa9b Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Thu, 7 Dec 2023 18:42:53 -0500 Subject: [PATCH 19/50] Implemented "Default Settings" section of Notebooks tab --- Source/Chatbook/PreferencesContent.wl | 455 +++++++++++++++++++++++++- Source/Chatbook/Services.wl | 1 + Source/Chatbook/UI.wl | 21 +- 3 files changed, 457 insertions(+), 20 deletions(-) diff --git a/Source/Chatbook/PreferencesContent.wl b/Source/Chatbook/PreferencesContent.wl index 3c23f516..ee46a2ff 100644 --- a/Source/Chatbook/PreferencesContent.wl +++ b/Source/Chatbook/PreferencesContent.wl @@ -25,13 +25,12 @@ Needs[ "Wolfram`Chatbook`UI`" ]; (* ::**************************************************************************************************************:: *) (* ::Section::Closed:: *) (*Configuration*) -$verticalSpacer = { Pane[ "", ImageSize -> { Automatic, 20 } ], SpanFromLeft }; $preferencesPages = { "Notebooks", "Services", "Personas", "Tools" }; $$preferencesPage = Alternatives @@ $preferencesPages; (* ::**************************************************************************************************************:: *) (* ::Section::Closed:: *) -(*Content*) +(*Main*) (* ::**************************************************************************************************************:: *) (* ::Subsection::Closed:: *) @@ -85,7 +84,7 @@ createPreferencesContent[ ] := Enclose[ ]; (* ::**************************************************************************************************************:: *) -(* ::Subsubsection::Closed:: *) +(* ::Subsection::Closed:: *) (*preferencesContent*) preferencesContent // beginDefinition; preferencesContent[ "Notebooks" ] := trackedDynamic[ notebookSettingsPanel[ ], { "Models" } ]; @@ -95,7 +94,11 @@ preferencesContent[ "Tools" ] := toolSettingsPanel[ ]; preferencesContent // endDefinition; (* ::**************************************************************************************************************:: *) -(* ::Subsubsection::Closed:: *) +(* ::Section::Closed:: *) +(*Notebooks*) + +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) (*notebookSettingsPanel*) notebookSettingsPanel // beginDefinition; @@ -103,7 +106,7 @@ notebookSettingsPanel[ ] := Pane[ DynamicModule[ { display = ProgressIndicator[ Appearance -> "Percolate" ] }, Dynamic[ display ], - Initialization :> (display = makeFrontEndAndNotebookSettingsContent @ $FrontEnd), + Initialization :> (display = createNotebookSettingsPanel[ ]), SynchronousInitialization -> False ], FrameMargins -> { { 8, 8 }, { 13, 13 } }, @@ -112,8 +115,334 @@ notebookSettingsPanel[ ] := Pane[ notebookSettingsPanel // endDefinition; +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*createNotebookSettingsPanel*) +createNotebookSettingsPanel // beginDefinition; + +createNotebookSettingsPanel[ ] := Enclose[ + Module[ { defaultSettingsLabel, defaultSettingsContent, interfaceLabel, interfaceContent }, + + defaultSettingsLabel = Style[ "Default Settings", "subsectionText" ]; + + defaultSettingsContent = ConfirmMatch[ + trackedDynamic[ makeDefaultSettingsContent[ ], "Preferences" ], + Except[ _makeDefaultSettingsContent ], + "DefaultSettings" + ]; + + interfaceLabel = Style[ "Chat Notebook Interface", "subsectionText" ]; + + interfaceContent = ConfirmMatch[ + makeInterfaceContent[ ], + Except[ _makeInterfaceContent ], + "Interface" + ]; + + createNotebookSettingsPanel[ ] = Grid[ + { + { defaultSettingsLabel }, + { defaultSettingsContent }, + { Spacer[ 1 ] }, + { interfaceLabel }, + { interfaceContent } + }, + Alignment -> { Left, Baseline }, + Spacings -> { 0, 0.7 } + ] + ], + throwInternalFailure +]; + +createNotebookSettingsPanel // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*makeDefaultSettingsContent*) +makeDefaultSettingsContent // beginDefinition; + +makeDefaultSettingsContent[ ] := Enclose[ + Module[ { personaSelector, modelSelector, temperatureSlider, row }, + + personaSelector = ConfirmMatch[ makePersonaSelector[ ], _PopupMenu, "PersonaSelector" ]; + modelSelector = ConfirmMatch[ makeModelSelector[ ], _DynamicModule, "ModelSelector" ]; + temperatureSlider = ConfirmMatch[ makeTemperatureSlider[ ], _Slider, "TemperatureSlider" ]; + row = Row[ { ## }, Spacer[ 3 ] ] &; + + Grid[ + { + { row[ "Default Persona:" , personaSelector ] }, + { row[ modelSelector ] }, + { row[ "Default Temperature:", temperatureSlider ] } + }, + Alignment -> { Left, Baseline }, + Spacings -> { 0, 0.7 } + ] + ], + throwInternalFailure +]; + +makeDefaultSettingsContent // endDefinition; + +(* FIXME: temporary definitions *) +makeSnapshotModelCheckbox[ ] := Checkbox[ ]; +makeSnapshotModelHelp[ ] := Tooltip[ "?", "" ]; +makeTemperatureSlider[ ] := Slider[ ]; +makeInterfaceContent[ ] := "Test content, please ignore."; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*makePersonaSelector*) +makePersonaSelector // beginDefinition; + +makePersonaSelector[ ] := + makePersonaSelector @ GetPersonasAssociation[ ]; + +makePersonaSelector[ personas_Association? AssociationQ ] := + makePersonaSelector @ KeyValueMap[ personaPopupLabel, personas ]; + +makePersonaSelector[ personas: { (_String -> _).. } ] := PopupMenu[ + Dynamic[ + currentChatSettings[ $FrontEnd, "LLMEvaluator" ], + (CurrentValue[ $FrontEnd, { TaggingRules, "ChatNotebookSettings", "LLMEvaluator" } ] = #1) & + ], + personas +]; + +makePersonaSelector // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsubsection::Closed:: *) +(*personaPopupLabel*) +personaPopupLabel // beginDefinition; + +personaPopupLabel[ name_String, persona_Association ] := popupValue[ + name, + personaDisplayName[ name, persona ], + getPersonaMenuIcon[ persona, "Full" ] +]; + +personaPopupLabel // endDefinition; + (* ::**************************************************************************************************************:: *) (* ::Subsubsection::Closed:: *) +(*makeModelSelector*) +makeModelSelector // beginDefinition; + +makeModelSelector[ ] := + makeModelSelector @ $availableServices; + +makeModelSelector[ services_Association? AssociationQ ] := Enclose[ + DynamicModule[ { default, service, model, state, serviceSelector, modelSelector }, + + default = currentChatSettings[ $FrontEnd, "Model" ]; + service = ConfirmBy[ extractServiceName @ default, StringQ, "ServiceName" ]; + model = ConfirmBy[ extractModelName @ default , StringQ, "ModelName" ]; + state = If[ modelListCachedQ @ service, "Loaded", "Loading" ]; + + modelSelector = If[ state === "Loaded", + makeModelNameSelector[ Dynamic @ service, Dynamic @ model ], + "" + ]; + + serviceSelector = makeServiceSelector[ + Dynamic @ service, + Dynamic @ model, + Dynamic @ modelSelector, + Dynamic @ state, + services + ]; + + Row @ { + "Default LLM Service:", + Spacer[ 1 ], + serviceSelector, + Spacer[ 5 ], + "Default Model:", + Spacer[ 1 ], + Dynamic[ + If[ state === "Loading", $loadingPopupMenu, modelSelector ], + TrackedSymbols :> { state, modelSelector } + ] + }, + + Initialization :> ( + modelSelector = catchAlways @ makeModelNameSelector[ Dynamic @ service, Dynamic @ model ]; + state = "Loaded"; + ), + SynchronousInitialization -> False, + SynchronousUpdating -> False, + UnsavedVariables :> { state } + ], + throwInternalFailure +]; + +makeModelSelector // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsubsection::Closed:: *) +(*makeServiceSelector*) +makeServiceSelector // beginDefinition; + +makeServiceSelector[ + Dynamic[ service_ ], + Dynamic[ model_ ], + Dynamic[ modelSelector_ ], + Dynamic[ state_ ], + services_ +] := + PopupMenu[ + Dynamic[ + extractServiceName @ CurrentChatSettings[ $FrontEnd, "Model" ], + serviceSelectCallback[ Dynamic @ service, Dynamic @ model, Dynamic @ modelSelector, Dynamic @ state ] + ], + KeyValueMap[ popupValue[ #1, #2[ "Service" ], #2[ "Icon" ] ] &, services ] + ]; + +makeServiceSelector // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsubsubsection::Closed:: *) +(*serviceSelectCallback*) +serviceSelectCallback // beginDefinition; + +serviceSelectCallback[ Dynamic[ service_ ], Dynamic[ model_ ], Dynamic[ modelSelector_ ], Dynamic[ state_ ] ] := + serviceSelectCallback[ #1, Dynamic @ service, Dynamic @ model, Dynamic @ modelSelector, Dynamic @ state ] &; + +serviceSelectCallback[ + selected_String, (* The value chosen via PopupMenu *) + Dynamic[ service_Symbol ], + Dynamic[ model_Symbol ], + Dynamic[ modelSelector_Symbol ], + Dynamic[ state_Symbol ] +] := catchAlways[ + service = selected; + + (* Switch model name selector to loading view: *) + If[ ! modelListCachedQ @ selected, state = "Loading" ]; + + (* Now that a new service has been selected, switch the model name to a previously used value for this service + if available. If service has not been chosen before, determine the initial model from the registered service. *) + model = getServiceDefaultModel @ selected; + + (* Store the service/model in FE settings: *) + CurrentChatSettings[ $FrontEnd, "Model" ] = <| "Service" -> service, "Name" -> model |>; + + (* Finish loading the model name selector: *) + If[ state === "Loading", + SessionSubmit[ + modelSelector = makeModelNameSelector[ Dynamic @ service, Dynamic @ model ]; + state = "Loaded" + ], + modelSelector = makeModelNameSelector[ Dynamic @ service, Dynamic @ model ] + ] +]; + +serviceSelectCallback // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsubsection::Closed:: *) +(*makeModelNameSelector*) +makeModelNameSelector // beginDefinition; + +makeModelNameSelector[ Dynamic[ service_ ], Dynamic[ model_ ] ] := Enclose[ + Module[ { models, current, default, fallback }, + + ensureServiceName @ service; + ConfirmAssert[ StringQ @ service, "ServiceName" ]; + + models = ConfirmMatch[ getServiceModelList @ service, { __Association }, "ServiceModelList" ]; + current = extractModelName @ CurrentChatSettings[ $FrontEnd, "Model" ]; + default = ConfirmBy[ getServiceDefaultModel @ service, StringQ, "DefaultName" ]; + fallback = <| "Service" -> service, "Name" -> default |>; + + If[ ! MemberQ[ models, KeyValuePattern[ "Name" -> current ] ], + CurrentValue[ $FrontEnd, { TaggingRules, "ChatNotebookSettings", "Model" } ] = fallback + ]; + + With[ { m = fallback }, + PopupMenu[ + Dynamic[ + Replace[ + extractModelName @ CurrentChatSettings[ $FrontEnd, "Model" ], + { + Except[ _String ] :> ( + CurrentValue[ $FrontEnd, { TaggingRules, "ChatNotebookSettings", "Model" } ] = m + ) + } + ], + modelSelectCallback[ Dynamic @ service, Dynamic @ model ] + ], + Map[ popupValue[ #[ "Name" ], #[ "DisplayName" ], #[ "Icon" ] ] &, models ], + ImageSize -> Automatic + ] + ] + ], + throwInternalFailure +]; + +makeModelNameSelector // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsubsubsection::Closed:: *) +(*modelSelectCallback*) +modelSelectCallback // beginDefinition; + +modelSelectCallback[ Dynamic[ service_ ], Dynamic[ model_ ] ] := + modelSelectCallback[ #1, Dynamic @ service, Dynamic @ model ] &; + +modelSelectCallback[ + selected_String, (* The value chosen via PopupMenu *) + Dynamic[ service_Symbol ], + Dynamic[ model_Symbol ] +] := catchAlways @ Enclose[ + model = selected; + + ensureServiceName @ service; + ConfirmAssert[ StringQ @ service, "ServiceName" ]; + + (* Remember the selected model for the given service, so it will be automatically chosen + when choosing this service again: *) + CurrentValue[ $FrontEnd, { TaggingRules, "ChatNotebookSettings", "ServiceDefaultModel", service } ] = model; + + (* Store the service/model in FE settings: *) + CurrentValue[ $FrontEnd, { TaggingRules, "ChatNotebookSettings", "Model" } ] = <| + "Service" -> service, + "Name" -> model + |> + , + throwInternalFailure +]; + +modelSelectCallback // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsubsection::Closed:: *) +(*makeTemperatureSlider*) +makeTemperatureSlider // beginDefinition; + +makeTemperatureSlider[ ] := + Slider[ + Dynamic[ CurrentChatSettings[ $FrontEnd, "Temperature" ] ], + { 0, 2, 0.01 }, + ImageSize -> { 135, Automatic }, + ImageMargins -> { { 5, 0 }, { 5, 5 } }, + Appearance -> "Labeled" + ]; + +makeTemperatureSlider // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Section::Closed:: *) +(*Services*) +(* TODO *) + +(* ::**************************************************************************************************************:: *) +(* ::Section::Closed:: *) +(*Personas*) + +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) (*personaSettingsPanel*) personaSettingsPanel // beginDefinition; @@ -129,7 +458,11 @@ personaSettingsPanel[ ] := personaSettingsPanel // endDefinition; (* ::**************************************************************************************************************:: *) -(* ::Subsubsection::Closed:: *) +(* ::Section::Closed:: *) +(*Tools*) + +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) (*toolSettingsPanel*) toolSettingsPanel // beginDefinition; @@ -144,6 +477,104 @@ toolSettingsPanel[ ] := toolSettingsPanel // endDefinition; +(* ::**************************************************************************************************************:: *) +(* ::Section::Closed:: *) +(*Common*) + +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*popupValue*) +popupValue // beginDefinition; + +popupValue[ value_String ] := + value -> value; + +popupValue[ value_String, label: Except[ $$unspecified ] ] := + value -> label; + +popupValue[ value_String, label: Except[ $$unspecified ], icon: Except[ $$unspecified ] ] := + value -> Row[ { resizeMenuIcon @ inlineTemplateBoxes @ icon, label }, Spacer[ 1 ] ]; + +popupValue // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*ensureServiceName*) +ensureServiceName // beginDefinition; +ensureServiceName // Attributes = { HoldFirst }; + +ensureServiceName[ symbol_Symbol ] := + With[ { service = symbol }, + service /; StringQ @ service + ]; + +ensureServiceName[ symbol_Symbol ] := + With[ { service = extractServiceName @ CurrentChatSettings[ $FrontEnd, "Model" ] }, + (symbol = service) /; StringQ @ service + ]; + +ensureServiceName // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*extractServiceName*) +extractServiceName // beginDefinition; +extractServiceName[ _String ] := "OpenAI"; +extractServiceName[ KeyValuePattern[ "Service" -> service_String ] ] := service; +extractServiceName[ _ ] := $DefaultModel[ "Service" ]; +extractServiceName // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*extractModelName*) +extractModelName // beginDefinition; +extractModelName[ name_String ] := name; +extractModelName[ KeyValuePattern[ "Name" -> name_String ] ] := name; +extractModelName[ _ ] := $DefaultModel[ "Name" ]; +extractModelName // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*getServiceDefaultModel*) +getServiceDefaultModel // beginDefinition; + +getServiceDefaultModel[ selected_String ] := Replace[ + (* Use the last model name that was selected for this service if it exists: *) + CurrentValue[ + $FrontEnd, + { TaggingRules, "ChatNotebookSettings", "ServiceDefaultModel", selected } + ], + + (* Otherwise determine a starting model from the registered service: *) + $$unspecified :> ( + CurrentValue[ + $FrontEnd, + { TaggingRules, "ChatNotebookSettings", "ServiceDefaultModel", selected } + ] = chooseDefaultModelName @ selected + ) +]; + +getServiceDefaultModel // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsubsubsection::Closed:: *) +(*chooseDefaultModelName*) +(* + Choose a default initial model according to the following rules: + 1. If the service name is the same as the one in $DefaultModel, use the model name in $DefaultModel. + 2. If the registered service specifies a "DefaultModel" property, we'll use that. + 3. If the model list is already cached for the service, we'll use the first model in that list. + 4. Otherwise, give Automatic to indicate a model name that must be resolved later. +*) +chooseDefaultModelName // beginDefinition; +chooseDefaultModelName[ service_String ] /; service === $DefaultModel[ "Service" ] := $DefaultModel[ "Name" ]; +chooseDefaultModelName[ service_String ] := chooseDefaultModelName @ $availableServices @ service; +chooseDefaultModelName[ KeyValuePattern[ "DefaultModel" -> model_ ] ] := toModelName @ model; +chooseDefaultModelName[ KeyValuePattern[ "CachedModels" -> models_List ] ] := chooseDefaultModelName @ models; +chooseDefaultModelName[ { model_, ___ } ] := toModelName @ model; +chooseDefaultModelName[ service_ ] := Automatic; +chooseDefaultModelName // endDefinition; + (* ::**************************************************************************************************************:: *) (* ::Subsubsection::Closed:: *) (*makeFrontEndAndNotebookSettingsContent*) @@ -341,6 +772,16 @@ makeOpenAIAPICompletionURLForm // endDefinition; (* ::Section::Closed:: *) (*UI Elements*) +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*$loadingPopupMenu*) +$loadingPopupMenu = PopupMenu[ "x", { "x" -> ProgressIndicator[ Appearance -> "Percolate" ] }, Enabled -> False ]; + +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*$verticalSpacer*) +$verticalSpacer = { Pane[ "", ImageSize -> { Automatic, 20 } ], SpanFromLeft }; + (* ::**************************************************************************************************************:: *) (* ::Subsection::Closed:: *) (*$resetButton*) @@ -378,7 +819,7 @@ $resetButton = ]; (* ::**************************************************************************************************************:: *) -(* ::Subsection::Closed:: *) +(* ::Subsubsection::Closed:: *) (*resetChatPreferences*) resetChatPreferences // beginDefinition; diff --git a/Source/Chatbook/Services.wl b/Source/Chatbook/Services.wl index a953d621..b2dbdab2 100644 --- a/Source/Chatbook/Services.wl +++ b/Source/Chatbook/Services.wl @@ -7,6 +7,7 @@ BeginPackage[ "Wolfram`Chatbook`Services`" ]; HoldComplete[ `$availableServices; `$enableLLMServices; + `$serviceCache; `$servicesLoaded; `$useLLMServices; `getAvailableServiceNames; diff --git a/Source/Chatbook/UI.wl b/Source/Chatbook/UI.wl index 6becde36..bc6a4eb1 100644 --- a/Source/Chatbook/UI.wl +++ b/Source/Chatbook/UI.wl @@ -23,18 +23,19 @@ CreateToolbarContent[] is called by the NotebookToolbar to generate the content "] HoldComplete[ + `getModelMenuIcon; `getPersonaIcon; `getPersonaMenuIcon; + `labeledCheckbox; + `makeAutomaticResultAnalysisCheckbox; + `makeTemperatureSlider; + `makeToolCallFrequencySlider; + `modelGroupName; `personaDisplayName; `resizeMenuIcon; `serviceIcon; - `tr; - `getModelMenuIcon; - `makeToolCallFrequencySlider; - `makeTemperatureSlider; - `labeledCheckbox; `showSnapshotModelsQ; - `makeAutomaticResultAnalysisCheckbox; + `tr; ]; Begin["`Private`"] @@ -1081,7 +1082,7 @@ serviceIcon[ KeyValuePattern[ "Service" -> service_String ] ] := serviceIcon[ "OpenAI" ] := chatbookIcon[ "ServiceIconOpenAI" , True ]; serviceIcon[ "Anthropic" ] := chatbookIcon[ "ServiceIconAnthropic", True ]; serviceIcon[ "PaLM" ] := chatbookIcon[ "ServiceIconPaLM" , True ]; -serviceIcon[ service_String ] := ""; +serviceIcon[ service_String ] := Replace[ $availableServices[ service, "Icon" ], $$unspecified -> "" ]; serviceIcon // endDefinition; @@ -1166,12 +1167,6 @@ menuModelGroup[ obj_, root_, currentModel_ ] := menuModelGroup[ obj_, root_, currentModel_, None, models_List ] := modelMenuItem[ obj, root, currentModel ] /@ models; -menuModelGroup[ obj_, root_, currentModel_, "Snapshot Models", models_List ] := - If[ TrueQ @ showSnapshotModelsQ[ ], - Join[ { "Snapshot Models" }, modelMenuItem[ obj, root, currentModel ] /@ models ], - { } - ]; - menuModelGroup[ obj_, root_, currentModel_, name_String, models_List ] := Join[ { name }, modelMenuItem[ obj, root, currentModel ] /@ models ]; From e48a11d44df74bb9b7f303fc06ca5f414f94179c Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Thu, 7 Dec 2023 18:48:55 -0500 Subject: [PATCH 20/50] Formatting --- Source/Chatbook/PreferencesContent.wl | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/Source/Chatbook/PreferencesContent.wl b/Source/Chatbook/PreferencesContent.wl index ee46a2ff..14b5c09e 100644 --- a/Source/Chatbook/PreferencesContent.wl +++ b/Source/Chatbook/PreferencesContent.wl @@ -235,10 +235,10 @@ makeModelSelector[ ] := makeModelSelector[ services_Association? AssociationQ ] := Enclose[ DynamicModule[ { default, service, model, state, serviceSelector, modelSelector }, - default = currentChatSettings[ $FrontEnd, "Model" ]; - service = ConfirmBy[ extractServiceName @ default, StringQ, "ServiceName" ]; - model = ConfirmBy[ extractModelName @ default , StringQ, "ModelName" ]; - state = If[ modelListCachedQ @ service, "Loaded", "Loading" ]; + default = currentChatSettings[ $FrontEnd, "Model" ]; + service = ConfirmBy[ extractServiceName @ default, StringQ, "ServiceName" ]; + model = ConfirmBy[ extractModelName @ default , StringQ, "ModelName" ]; + state = If[ modelListCachedQ @ service, "Loaded", "Loading" ]; modelSelector = If[ state === "Loaded", makeModelNameSelector[ Dynamic @ service, Dynamic @ model ], From 801bb12c110f6db47136cfc11b5f92392c0452e5 Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Thu, 7 Dec 2023 18:52:37 -0500 Subject: [PATCH 21/50] Remove unused definitions and add missing dynamic update --- Source/Chatbook/PreferencesContent.wl | 11 ++++------- 1 file changed, 4 insertions(+), 7 deletions(-) diff --git a/Source/Chatbook/PreferencesContent.wl b/Source/Chatbook/PreferencesContent.wl index 14b5c09e..0d2f024d 100644 --- a/Source/Chatbook/PreferencesContent.wl +++ b/Source/Chatbook/PreferencesContent.wl @@ -185,9 +185,7 @@ makeDefaultSettingsContent[ ] := Enclose[ makeDefaultSettingsContent // endDefinition; (* FIXME: temporary definitions *) -makeSnapshotModelCheckbox[ ] := Checkbox[ ]; makeSnapshotModelHelp[ ] := Tooltip[ "?", "" ]; -makeTemperatureSlider[ ] := Slider[ ]; makeInterfaceContent[ ] := "Test content, please ignore."; (* ::**************************************************************************************************************:: *) @@ -823,31 +821,30 @@ $resetButton = (*resetChatPreferences*) resetChatPreferences // beginDefinition; -resetChatPreferences[ "Notebooks" ] := +resetChatPreferences[ "Notebooks" ] := ( FrontEndExecute @ FrontEnd`RemoveOptions[ $FrontEnd, { System`LLMEvaluator, { TaggingRules, "ChatNotebookSettings" } } ]; + updateDynamics[ "Preferences" ]; +); resetChatPreferences[ "Personas" ] := With[ { path = Sequence[ PrivateFrontEndOptions, "InterfaceSettings", "Chatbook" ] }, (* TODO: choice dialog to uninstall personas *) - resetChatPreferences[ "Notebooks" ]; CurrentValue[ $FrontEnd, { path, "VisiblePersonas" } ] = $corePersonaNames; CurrentValue[ $FrontEnd, { path, "PersonaFavorites" } ] = $corePersonaNames; - updateDynamics[ "Preferences" ]; + resetChatPreferences[ "Notebooks" ]; ]; resetChatPreferences[ "Tools" ] := ( (* TODO: choice dialog to uninstall tools *) resetChatPreferences[ "Notebooks" ]; - updateDynamics[ "Preferences" ]; ); resetChatPreferences[ "Services" ] := ( (* TODO: choice dialog to clear service connections *) resetChatPreferences[ "Notebooks" ]; - updateDynamics[ "Preferences" ]; ); resetChatPreferences // endDefinition; From 9dbc2ac2cc74c1a529588a896fdbb7c888b81a3d Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Thu, 7 Dec 2023 20:14:52 -0500 Subject: [PATCH 22/50] Bugfix: avoid internal failure if attached cell has already been deleted --- Source/Chatbook/Menus.wl | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/Source/Chatbook/Menus.wl b/Source/Chatbook/Menus.wl index 9298af75..ebe37c5c 100644 --- a/Source/Chatbook/Menus.wl +++ b/Source/Chatbook/Menus.wl @@ -224,6 +224,10 @@ removeChatMenus[ cell_CellObject ] /; MemberQ[ cellStyles @ cell, "AttachedChatM removeChatMenus[ cell_CellObject ] := NotebookDelete @ Cells[ cell, AttachedCell -> True, CellStyle -> "AttachedChatMenu" ]; +(* Cell has already been removed: *) +removeChatMenus[ $Failed ] := + Null; + removeChatMenus // endDefinition; (* ::**************************************************************************************************************:: *) From 829dbb0f3763d6c03f4795186c4a1234f3676a74 Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Fri, 8 Dec 2023 08:12:24 -0500 Subject: [PATCH 23/50] Remove temporary definition --- Source/Chatbook/PreferencesContent.wl | 1 - 1 file changed, 1 deletion(-) diff --git a/Source/Chatbook/PreferencesContent.wl b/Source/Chatbook/PreferencesContent.wl index 0d2f024d..13b48d54 100644 --- a/Source/Chatbook/PreferencesContent.wl +++ b/Source/Chatbook/PreferencesContent.wl @@ -185,7 +185,6 @@ makeDefaultSettingsContent[ ] := Enclose[ makeDefaultSettingsContent // endDefinition; (* FIXME: temporary definitions *) -makeSnapshotModelHelp[ ] := Tooltip[ "?", "" ]; makeInterfaceContent[ ] := "Test content, please ignore."; (* ::**************************************************************************************************************:: *) From f0812fc4cb210dae41f8ebaeafd47b0e05791d7c Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Fri, 8 Dec 2023 08:13:20 -0500 Subject: [PATCH 24/50] GPT-4 commentary --- Source/Chatbook/PreferencesContent.wl | 74 +++++++++++++++++++++------ 1 file changed, 57 insertions(+), 17 deletions(-) diff --git a/Source/Chatbook/PreferencesContent.wl b/Source/Chatbook/PreferencesContent.wl index 13b48d54..654ec5a5 100644 --- a/Source/Chatbook/PreferencesContent.wl +++ b/Source/Chatbook/PreferencesContent.wl @@ -35,14 +35,19 @@ $$preferencesPage = Alternatives @@ $preferencesPages; (* ::**************************************************************************************************************:: *) (* ::Subsection::Closed:: *) (*createPreferencesContent*) +(* Displays all the content found in the "AI Settings" tab in the preferences dialog. *) +createPreferencesContent // beginDefinition; + createPreferencesContent[ ] := Enclose[ Module[ { notebookSettings, serviceSettings, personaSettings, toolSettings, tabView, reset }, - notebookSettings = ConfirmMatch[ preferencesContent[ "Notebooks" ], _Dynamic|_DynamicModule, "Notebooks" ]; - serviceSettings = ConfirmMatch[ preferencesContent[ "Services" ], _Dynamic|_DynamicModule, "Services" ]; - personaSettings = ConfirmMatch[ preferencesContent[ "Personas" ], _Dynamic|_DynamicModule, "Personas" ]; - toolSettings = ConfirmMatch[ preferencesContent[ "Tools" ], _Dynamic|_DynamicModule, "Tools" ]; + (* Retrieve the dynamic content for each preferences tab, confirming that it matches the expected types: *) + notebookSettings = ConfirmMatch[ preferencesContent[ "Notebooks" ], _Dynamic | _DynamicModule, "Notebooks" ]; + serviceSettings = ConfirmMatch[ preferencesContent[ "Services" ], _Dynamic | _DynamicModule, "Services" ]; + personaSettings = ConfirmMatch[ preferencesContent[ "Personas" ], _Dynamic | _DynamicModule, "Personas" ]; + toolSettings = ConfirmMatch[ preferencesContent[ "Tools" ], _Dynamic | _DynamicModule, "Tools" ]; + (* Create a TabView for the preferences content, with the tab state stored in the FE's private options: *) tabView = TabView[ { { "Notebooks", "Notebooks" -> notebookSettings }, @@ -59,11 +64,13 @@ createPreferencesContent[ ] := Enclose[ FrameMargins -> { { 2, 2 }, { 2, 3 } }, ImageMargins -> { { 10, 10 }, { 2, 2 } }, ImageSize -> { 640, Automatic }, - LabelStyle -> "feTabView" + LabelStyle -> "feTabView" (* Defined in the SystemDialog stylesheet: *) ]; + (* Create a reset button that will reset preferences to default settings: *) reset = Pane[ $resetButton, ImageMargins -> { { 20, 0 }, { 0, 10 } }, ImageSize -> 640 ]; + (* Arrange the TabView and reset button in a Grid layout with vertical spacers: *) Grid[ { $verticalSpacer, @@ -73,7 +80,7 @@ createPreferencesContent[ ] := Enclose[ $verticalSpacer }, Alignment -> Left, - BaseStyle -> "defaultGrid", + BaseStyle -> "defaultGrid", (* Defined in the SystemDialog stylesheet *) AutoDelete -> False, FrameStyle -> { AbsoluteThickness[ 1 ], GrayLevel[ 0.898 ] }, Dividers -> { False, { 4 -> True } }, @@ -83,14 +90,27 @@ createPreferencesContent[ ] := Enclose[ throwInternalFailure ]; +createPreferencesContent // endDefinition; + (* ::**************************************************************************************************************:: *) (* ::Subsection::Closed:: *) (*preferencesContent*) +(* Define dynamic content for each of the preferences tabs. *) preferencesContent // beginDefinition; + +(* Content for the "Notebooks" tab: *) preferencesContent[ "Notebooks" ] := trackedDynamic[ notebookSettingsPanel[ ], { "Models" } ]; -preferencesContent[ "Personas" ] := trackedDynamic[ personaSettingsPanel[ ], { "Personas" } ]; -preferencesContent[ "Services" ] := trackedDynamic[ "Coming soon.", { "Models" } ]; -preferencesContent[ "Tools" ] := toolSettingsPanel[ ]; + +(* Content for the "Personas" tab: *) +preferencesContent[ "Personas" ] := trackedDynamic[ personaSettingsPanel[ ], { "Personas" } ]; + +(* Content for the "Services" tab: *) +(* FIXME: this is placeholder code *) +preferencesContent[ "Services" ] := trackedDynamic[ "Coming soon.", { "Models" } ]; + +(* Content for the "Tools" tab: *) +preferencesContent[ "Tools" ] := toolSettingsPanel[ ]; + preferencesContent // endDefinition; (* ::**************************************************************************************************************:: *) @@ -104,8 +124,10 @@ notebookSettingsPanel // beginDefinition; notebookSettingsPanel[ ] := Pane[ DynamicModule[ + (* Display a progress indicator until content is loaded via initialization: *) { display = ProgressIndicator[ Appearance -> "Percolate" ] }, Dynamic[ display ], + (* createNotebookSettingsPanel is called to initialize the content of the panel: *) Initialization :> (display = createNotebookSettingsPanel[ ]), SynchronousInitialization -> False ], @@ -121,25 +143,31 @@ notebookSettingsPanel // endDefinition; createNotebookSettingsPanel // beginDefinition; createNotebookSettingsPanel[ ] := Enclose[ - Module[ { defaultSettingsLabel, defaultSettingsContent, interfaceLabel, interfaceContent }, + Module[ { defaultSettingsLabel, defaultSettingsContent, interfaceLabel, interfaceContent, content }, + (* Label for the default settings section using a style from SystemDialog.nb: *) defaultSettingsLabel = Style[ "Default Settings", "subsectionText" ]; + (* Retrieve and confirm the content for default settings: *) defaultSettingsContent = ConfirmMatch[ trackedDynamic[ makeDefaultSettingsContent[ ], "Preferences" ], - Except[ _makeDefaultSettingsContent ], + _Dynamic, "DefaultSettings" ]; + (* Label for the interface section using a style from SystemDialog.nb: *) interfaceLabel = Style[ "Chat Notebook Interface", "subsectionText" ]; + (* Retrieve and confirm the content for the chat notebook interface, + ensuring it is not an error from makeInterfaceContent: *) interfaceContent = ConfirmMatch[ makeInterfaceContent[ ], Except[ _makeInterfaceContent ], "Interface" ]; - createNotebookSettingsPanel[ ] = Grid[ + (* Assemble the default settings and interface content into a grid layout: *) + content = Grid[ { { defaultSettingsLabel }, { defaultSettingsContent }, @@ -149,7 +177,10 @@ createNotebookSettingsPanel[ ] := Enclose[ }, Alignment -> { Left, Baseline }, Spacings -> { 0, 0.7 } - ] + ]; + + (* Cache the content in case panel is redrawn: *) + createNotebookSettingsPanel[ ] = content ], throwInternalFailure ]; @@ -163,12 +194,16 @@ makeDefaultSettingsContent // beginDefinition; makeDefaultSettingsContent[ ] := Enclose[ Module[ { personaSelector, modelSelector, temperatureSlider, row }, - - personaSelector = ConfirmMatch[ makePersonaSelector[ ], _PopupMenu, "PersonaSelector" ]; - modelSelector = ConfirmMatch[ makeModelSelector[ ], _DynamicModule, "ModelSelector" ]; + (* The personaSelector is a pop-up menu for selecting the default persona: *) + personaSelector = ConfirmMatch[ makePersonaSelector[ ], _PopupMenu, "PersonaSelector" ]; + (* The modelSelector is a dynamic module containing menus to select the service and model separately: *) + modelSelector = ConfirmMatch[ makeModelSelector[ ], _DynamicModule, "ModelSelector" ]; + (* The temperatureSlider is a control for setting the default 'temperature' for responses: *) temperatureSlider = ConfirmMatch[ makeTemperatureSlider[ ], _Slider, "TemperatureSlider" ]; - row = Row[ { ## }, Spacer[ 3 ] ] &; + (* Helper function to create a row layout with spacers between elements: *) + row = Row[ { ## }, Spacer[ 3 ] ] &; + (* Assemble the persona selector, model selector, and temperature slider into a grid layout: *) Grid[ { { row[ "Default Persona:" , personaSelector ] }, @@ -192,12 +227,17 @@ makeInterfaceContent[ ] := "Test content, please ignore."; (*makePersonaSelector*) makePersonaSelector // beginDefinition; +(* Top-level function without arguments, calls the version with personas from GetPersonasAssociation *) makePersonaSelector[ ] := makePersonaSelector @ GetPersonasAssociation[ ]; +(* Overload of makePersonaSelector that takes an Association of personas, + converts it to a list of labels for PopupMenu *) makePersonaSelector[ personas_Association? AssociationQ ] := makePersonaSelector @ KeyValueMap[ personaPopupLabel, personas ]; +(* Overload of makePersonaSelector that takes a list of rules where each rule is a string to an association, + creates a PopupMenu with this list *) makePersonaSelector[ personas: { (_String -> _).. } ] := PopupMenu[ Dynamic[ currentChatSettings[ $FrontEnd, "LLMEvaluator" ], From dd09c867a74c56c4b487f3b6d7a0e8c117f7583e Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Sat, 9 Dec 2023 10:23:59 -0500 Subject: [PATCH 25/50] Added more content to notebooks tab --- Source/Chatbook/PreferencesContent.wl | 380 ++++++++++++++++++++++++-- 1 file changed, 357 insertions(+), 23 deletions(-) diff --git a/Source/Chatbook/PreferencesContent.wl b/Source/Chatbook/PreferencesContent.wl index 654ec5a5..e809a8dc 100644 --- a/Source/Chatbook/PreferencesContent.wl +++ b/Source/Chatbook/PreferencesContent.wl @@ -143,7 +143,13 @@ notebookSettingsPanel // endDefinition; createNotebookSettingsPanel // beginDefinition; createNotebookSettingsPanel[ ] := Enclose[ - Module[ { defaultSettingsLabel, defaultSettingsContent, interfaceLabel, interfaceContent, content }, + Module[ + { + defaultSettingsLabel, defaultSettingsContent, + interfaceLabel, interfaceContent, + featuresLabel, featuresContent, + content + }, (* Label for the default settings section using a style from SystemDialog.nb: *) defaultSettingsLabel = Style[ "Default Settings", "subsectionText" ]; @@ -166,16 +172,34 @@ createNotebookSettingsPanel[ ] := Enclose[ "Interface" ]; + (* Label for the features section using a style from SystemDialog.nb: *) + featuresLabel = Style[ "Features", "subsectionText" ]; + + (* Retrieve and confirm the content for the chat notebook features, + ensuring it is not an error from makeFeaturesContent: *) + featuresContent = ConfirmMatch[ + makeFeaturesContent[ ], + Except[ _makeFeaturesContent ], + "Features" + ]; + (* Assemble the default settings and interface content into a grid layout: *) content = Grid[ { { defaultSettingsLabel }, { defaultSettingsContent }, { Spacer[ 1 ] }, + { Spacer[ 1 ] }, { interfaceLabel }, - { interfaceContent } + { interfaceContent }, + { Spacer[ 1 ] }, + { Spacer[ 1 ] }, + { featuresLabel }, + { featuresContent } }, Alignment -> { Left, Baseline }, + Dividers -> { False, { 4 -> True, 8 -> True } }, + ItemSize -> { Fit, Automatic }, Spacings -> { 0, 0.7 } ]; @@ -193,22 +217,25 @@ createNotebookSettingsPanel // endDefinition; makeDefaultSettingsContent // beginDefinition; makeDefaultSettingsContent[ ] := Enclose[ - Module[ { personaSelector, modelSelector, temperatureSlider, row }, + Module[ { personaSelector, modelSelector, assistanceCheckbox, temperatureInput, row }, (* The personaSelector is a pop-up menu for selecting the default persona: *) personaSelector = ConfirmMatch[ makePersonaSelector[ ], _PopupMenu, "PersonaSelector" ]; (* The modelSelector is a dynamic module containing menus to select the service and model separately: *) modelSelector = ConfirmMatch[ makeModelSelector[ ], _DynamicModule, "ModelSelector" ]; - (* The temperatureSlider is a control for setting the default 'temperature' for responses: *) - temperatureSlider = ConfirmMatch[ makeTemperatureSlider[ ], _Slider, "TemperatureSlider" ]; + (* Checkbox to enable automatic assistance for normal shift-enter evaluations: *) + assistanceCheckbox = ConfirmMatch[ makeAssistanceCheckbox[ ], _Grid|_Row, "AssistanceCheckbox" ]; + (* The temperatureInput is an input field for setting the default 'temperature' for responses: *) + temperatureInput = ConfirmMatch[ makeTemperatureInput[ ], _Grid, "TemperatureInput" ]; (* Helper function to create a row layout with spacers between elements: *) row = Row[ { ## }, Spacer[ 3 ] ] &; (* Assemble the persona selector, model selector, and temperature slider into a grid layout: *) Grid[ { - { row[ "Default Persona:" , personaSelector ] }, - { row[ modelSelector ] }, - { row[ "Default Temperature:", temperatureSlider ] } + { row[ "Default Persona:", personaSelector ] }, + { modelSelector }, + { assistanceCheckbox }, + { temperatureInput } }, Alignment -> { Left, Baseline }, Spacings -> { 0, 0.7 } @@ -219,9 +246,6 @@ makeDefaultSettingsContent[ ] := Enclose[ makeDefaultSettingsContent // endDefinition; -(* FIXME: temporary definitions *) -makeInterfaceContent[ ] := "Test content, please ignore."; - (* ::**************************************************************************************************************:: *) (* ::Subsubsection::Closed:: *) (*makePersonaSelector*) @@ -454,20 +478,251 @@ modelSelectCallback[ modelSelectCallback // endDefinition; (* ::**************************************************************************************************************:: *) -(* ::Subsubsubsection::Closed:: *) -(*makeTemperatureSlider*) -makeTemperatureSlider // beginDefinition; - -makeTemperatureSlider[ ] := - Slider[ - Dynamic[ CurrentChatSettings[ $FrontEnd, "Temperature" ] ], - { 0, 2, 0.01 }, - ImageSize -> { 135, Automatic }, - ImageMargins -> { { 5, 0 }, { 5, 5 } }, - Appearance -> "Labeled" +(* ::Subsubsection::Closed:: *) +(*makeAssistanceCheckbox*) +makeAssistanceCheckbox // beginDefinition; + +makeAssistanceCheckbox[ ] := + prefsCheckbox[ + Dynamic[ + TrueQ @ CurrentChatSettings[ $FrontEnd, "Assistance" ], + (CurrentChatSettings[ $FrontEnd, "Assistance" ] = #1) & + ], + infoTooltip[ + "Enable automatic assistance", + "If enabled, automatic AI provided suggestions will be added following evaluation results." + ] ]; -makeTemperatureSlider // endDefinition; +makeAssistanceCheckbox // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*makeTemperatureInput*) +makeTemperatureInput // beginDefinition; + +makeTemperatureInput[ ] := + prefsInputField[ + "Temperature:", + Dynamic[ + CurrentChatSettings[ $FrontEnd, "Temperature" ], + { + None, + If[ NumberQ @ #, CurrentChatSettings[ $FrontEnd, "Temperature" ] = # ] & + } + ], + Number, + ImageSize -> { 50, Automatic } + ]; + +makeTemperatureInput // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*makeInterfaceContent*) +makeInterfaceContent // beginDefinition; + +makeInterfaceContent[ ] := Enclose[ + Module[ { formatCheckbox, includeHistory, chatHistoryLength, mergeMessages }, + + formatCheckbox = ConfirmMatch[ makeFormatCheckbox[ ], _Grid|_Row, "FormatCheckbox" ]; + includeHistory = ConfirmMatch[ makeIncludeHistoryCheckbox[ ], _Grid|_Row, "ChatHistory" ]; + chatHistoryLength = ConfirmMatch[ makeChatHistoryLengthInput[ ], _Grid|_Row, "ChatHistoryLength" ]; + mergeMessages = ConfirmMatch[ makeMergeMessagesCheckbox[ ], _Grid|_Row, "MergeMessages" ]; + + Grid[ + { + { formatCheckbox }, + { includeHistory }, + { chatHistoryLength }, + { mergeMessages } + }, + Alignment -> { Left, Baseline }, + Spacings -> { 0, 0.7 } + ] + ], + throwInternalFailure +]; + +makeInterfaceContent // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*makeFormatCheckbox*) +makeFormatCheckbox // beginDefinition; + +makeFormatCheckbox[ ] := + prefsCheckbox[ + Dynamic[ + TrueQ @ CurrentChatSettings[ $FrontEnd, "AutoFormat" ], + (CurrentChatSettings[ $FrontEnd, "AutoFormat" ] = #1) & + ], + "Format chat output" + ]; + +makeFormatCheckbox // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*makeIncludeHistoryCheckbox*) +makeIncludeHistoryCheckbox // beginDefinition; + +makeIncludeHistoryCheckbox[ ] := + prefsCheckbox[ + Dynamic[ + MatchQ[ CurrentChatSettings[ $FrontEnd, "IncludeHistory" ], True|Automatic ], + (CurrentChatSettings[ $FrontEnd, "IncludeHistory" ] = #1) & + ], + infoTooltip[ + "Include chat history", + "If enabled, cells preceding the chat input will be included as additional context for the LLM." + ] + ]; + +makeIncludeHistoryCheckbox // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*makeChatHistoryLengthInput*) +makeChatHistoryLengthInput // beginDefinition; + +makeChatHistoryLengthInput[ ] := + infoTooltip[ + prefsInputField[ + "Chat history length:", + Dynamic[ + CurrentChatSettings[ $FrontEnd, "ChatHistoryLength" ], + { + None, + If[ NumberQ @ #, CurrentChatSettings[ $FrontEnd, "ChatHistoryLength" ] = Floor[ # ] ] & + } + ], + Number, + ImageSize -> { 50, Automatic } + ], + "Maximum number of cells to include in chat history" + ]; + +makeChatHistoryLengthInput // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*makeMergeMessagesCheckbox*) +makeMergeMessagesCheckbox // beginDefinition; + +makeMergeMessagesCheckbox[ ] := + prefsCheckbox[ + Dynamic[ + MatchQ[ CurrentChatSettings[ $FrontEnd, "MergeMessages" ], True|Automatic ], + (CurrentChatSettings[ $FrontEnd, "MergeMessages" ] = #1) & + ], + infoTooltip[ + "Merge chat messages", + "If enabled, adjacent cells with the same author will be merged into a single chat message." + ] + ]; + +makeMergeMessagesCheckbox // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*makeFeaturesContent*) +makeFeaturesContent // beginDefinition; + +makeFeaturesContent[ ] := Enclose[ + Module[ { multimodal, toolsEnabled, toolFrequency }, + + multimodal = ConfirmMatch[ makeMultimodalMenu[ ], _Grid|_Row, "Multimodal" ]; + toolsEnabled = ConfirmMatch[ makeToolsEnabledMenu[ ], _Grid|_Row, "ToolsEnabled" ]; + toolFrequency = ConfirmMatch[ makeToolCallFrequencySelector[ ], _Grid|_Row, "ToolFrequency" ]; + + Grid[ + { + { multimodal }, + { toolsEnabled }, + { toolFrequency } + }, + Alignment -> { Left, Baseline }, + Spacings -> { 0, 0.7 } + ] + ], + throwInternalFailure +]; + +makeFeaturesContent // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*makeMultimodalMenu*) +makeMultimodalMenu // beginDefinition; + +makeMultimodalMenu[ ] := + Grid[ + { + { + Style[ "Enable multimodal content: ", "leadinText" ], + PopupMenu[ + Dynamic @ CurrentChatSettings[ $FrontEnd, "Multimodal" ], + { + Automatic -> "Automatic by model", + True -> "Always enabled", + False -> "Always disabled" + }, + MenuStyle -> "controlText" + ] + } + }, + Alignment -> { Left, Baseline }, + Spacings -> 0.5 + ]; + +makeMultimodalMenu // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*makeToolsEnabledMenu*) +makeToolsEnabledMenu // beginDefinition; + +makeToolsEnabledMenu[ ] := + Grid[ + { + { + Style[ "Enable tools: ", "leadinText" ], + PopupMenu[ + Dynamic @ CurrentChatSettings[ $FrontEnd, "ToolsEnabled" ], + { + Automatic -> "Automatic by model", + True -> "Always enabled", + False -> "Always disabled" + }, + MenuStyle -> "controlText" + ] + } + }, + Alignment -> { Left, Baseline }, + Spacings -> 0.5 + ]; + +makeToolsEnabledMenu // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*makeToolCallFrequencySelector*) +makeToolCallFrequencySelector // beginDefinition; + +makeToolCallFrequencySelector[ ] := + Grid[ + { + { + Style[ "Tool call frequency:", "leadinText" ], + makeToolCallFrequencySlider[ $FrontEnd ] + } + }, + Alignment -> { Left, Baseline }, + Spacings -> 0.5 + ]; + +makeToolCallFrequencySelector // endDefinition; (* ::**************************************************************************************************************:: *) (* ::Section::Closed:: *) @@ -518,6 +773,85 @@ toolSettingsPanel // endDefinition; (* ::Section::Closed:: *) (*Common*) +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*prefsInputField*) +prefsInputField // beginDefinition; + +(* cSpell: ignore leadin *) +prefsInputField[ label_, value_Dynamic, type_, opts: OptionsPattern[ ] ] := Grid[ + { { label, prefsInputField0[ value, type, opts ] } }, + Alignment -> { Automatic, Baseline }, + BaseStyle -> { "leadinText" }, + Spacings -> 0.5 +]; + +prefsInputField // endDefinition; + + +prefsInputField0 // beginDefinition; + +prefsInputField0[ value_Dynamic, type_, opts: OptionsPattern[ ] ] := RawBoxes @ StyleBox[ + TemplateBox[ + { + value, + type, + DeleteDuplicatesBy[ + Flatten @ { + opts, + Alignment -> { Left, Top }, + BaseStyle -> { "controlText" }, + ContinuousAction -> False, + ImageMargins -> { { Automatic, Automatic }, { Automatic, Automatic } } + }, + ToString @* First + ], + Automatic + }, + "InputFieldAppearance:RoundedFrame" + ], + FrameBoxOptions -> { BaselinePosition -> Top -> Scaled[ 1.3 ] } +]; + +prefsInputField0 // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*prefsCheckbox*) +prefsCheckbox // beginDefinition; + +prefsCheckbox[ value_Dynamic, label_, rest___ ] := + Grid[ + { { Checkbox[ value, rest ], clickableCheckboxLabel[ value, label ] } }, + Alignment -> { Left, Center }, + Spacings -> 0.2 + ]; + +prefsCheckbox // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*clickableCheckboxLabel*) +clickableCheckboxLabel // beginDefinition; + +clickableCheckboxLabel[ value_Dynamic, label_ ] := Toggler[ + value, + { True -> label, False -> label }, + BaselinePosition -> Scaled[ 0.2 ], + BaseStyle -> { "checkboxText" } +]; + +clickableCheckboxLabel // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*infoTooltip*) +infoTooltip // beginDefinition; +infoTooltip[ label_, tooltip_ ] := Row @ { label, Spacer[ 3 ], Tooltip[ $infoIcon, tooltip ] }; +infoTooltip // endDefinition; + +$infoIcon = chatbookIcon[ "InformationTooltip", False ]; + (* ::**************************************************************************************************************:: *) (* ::Subsection::Closed:: *) (*popupValue*) From f87a37d74b1d99428ff5dd5462a1aa6496bdd232 Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Mon, 11 Dec 2023 10:53:24 -0500 Subject: [PATCH 26/50] Added support for `OpenPreferencesDialog[tabID, highlightID]` --- Source/Chatbook/PreferencesContent.wl | 177 +++++++++++++++++--------- 1 file changed, 120 insertions(+), 57 deletions(-) diff --git a/Source/Chatbook/PreferencesContent.wl b/Source/Chatbook/PreferencesContent.wl index e809a8dc..baf5c79c 100644 --- a/Source/Chatbook/PreferencesContent.wl +++ b/Source/Chatbook/PreferencesContent.wl @@ -57,7 +57,7 @@ createPreferencesContent[ ] := Enclose[ }, Dynamic @ CurrentValue[ $FrontEnd, - { PrivateFrontEndOptions, "InterfaceSettings", "Chatbook", "PreferencesTab" }, + { PrivateFrontEndOptions, "DialogSettings", "Preferences", "TabSettings", "AI", "Top" }, "Notebooks" ], Background -> None, @@ -217,25 +217,23 @@ createNotebookSettingsPanel // endDefinition; makeDefaultSettingsContent // beginDefinition; makeDefaultSettingsContent[ ] := Enclose[ - Module[ { personaSelector, modelSelector, assistanceCheckbox, temperatureInput, row }, + Module[ { personaSelector, modelSelector, assistanceCheckbox, temperatureInput }, (* The personaSelector is a pop-up menu for selecting the default persona: *) - personaSelector = ConfirmMatch[ makePersonaSelector[ ], _PopupMenu, "PersonaSelector" ]; + personaSelector = ConfirmMatch[ makePersonaSelector[ ], _Style, "PersonaSelector" ]; (* The modelSelector is a dynamic module containing menus to select the service and model separately: *) modelSelector = ConfirmMatch[ makeModelSelector[ ], _DynamicModule, "ModelSelector" ]; (* Checkbox to enable automatic assistance for normal shift-enter evaluations: *) - assistanceCheckbox = ConfirmMatch[ makeAssistanceCheckbox[ ], _Grid|_Row, "AssistanceCheckbox" ]; + assistanceCheckbox = ConfirmMatch[ makeAssistanceCheckbox[ ], _Style, "AssistanceCheckbox" ]; (* The temperatureInput is an input field for setting the default 'temperature' for responses: *) - temperatureInput = ConfirmMatch[ makeTemperatureInput[ ], _Grid, "TemperatureInput" ]; - (* Helper function to create a row layout with spacers between elements: *) - row = Row[ { ## }, Spacer[ 3 ] ] &; + temperatureInput = ConfirmMatch[ makeTemperatureInput[ ], _Style, "TemperatureInput" ]; (* Assemble the persona selector, model selector, and temperature slider into a grid layout: *) Grid[ { - { row[ "Default Persona:", personaSelector ] }, - { modelSelector }, + { personaSelector }, + { modelSelector }, { assistanceCheckbox }, - { temperatureInput } + { temperatureInput } }, Alignment -> { Left, Baseline }, Spacings -> { 0, 0.7 } @@ -262,13 +260,22 @@ makePersonaSelector[ personas_Association? AssociationQ ] := (* Overload of makePersonaSelector that takes a list of rules where each rule is a string to an association, creates a PopupMenu with this list *) -makePersonaSelector[ personas: { (_String -> _).. } ] := PopupMenu[ - Dynamic[ - currentChatSettings[ $FrontEnd, "LLMEvaluator" ], - (CurrentValue[ $FrontEnd, { TaggingRules, "ChatNotebookSettings", "LLMEvaluator" } ] = #1) & - ], - personas -]; +makePersonaSelector[ personas: { (_String -> _).. } ] := + highlightControl[ + Row @ { + "Default Persona:", + Spacer[ 3 ], + PopupMenu[ + Dynamic[ + currentChatSettings[ $FrontEnd, "LLMEvaluator" ], + (CurrentValue[ $FrontEnd, { TaggingRules, "ChatNotebookSettings", "LLMEvaluator" } ] = #1) & + ], + personas + ] + }, + "Notebooks", + "DefaultPersona" + ]; makePersonaSelector // endDefinition; @@ -294,7 +301,7 @@ makeModelSelector[ ] := makeModelSelector @ $availableServices; makeModelSelector[ services_Association? AssociationQ ] := Enclose[ - DynamicModule[ { default, service, model, state, serviceSelector, modelSelector }, + DynamicModule[ { default, service, model, state, serviceSelector, modelSelector, highlight }, default = currentChatSettings[ $FrontEnd, "Model" ]; service = ConfirmBy[ extractServiceName @ default, StringQ, "ServiceName" ]; @@ -314,16 +321,18 @@ makeModelSelector[ services_Association? AssociationQ ] := Enclose[ services ]; + highlight = highlightControl[ Row @ { #1, Spacer[ 1 ], #2 }, "Notebooks", #3 ] &; + Row @ { - "Default LLM Service:", - Spacer[ 1 ], - serviceSelector, + highlight[ "Default LLM Service:", serviceSelector, "DefaultService" ], Spacer[ 5 ], - "Default Model:", - Spacer[ 1 ], - Dynamic[ - If[ state === "Loading", $loadingPopupMenu, modelSelector ], - TrackedSymbols :> { state, modelSelector } + highlight[ + "Default Model:", + Dynamic[ + If[ state === "Loading", $loadingPopupMenu, modelSelector ], + TrackedSymbols :> { state, modelSelector } + ], + "DefaultModel" ] }, @@ -482,7 +491,7 @@ modelSelectCallback // endDefinition; (*makeAssistanceCheckbox*) makeAssistanceCheckbox // beginDefinition; -makeAssistanceCheckbox[ ] := +makeAssistanceCheckbox[ ] := highlightControl[ prefsCheckbox[ Dynamic[ TrueQ @ CurrentChatSettings[ $FrontEnd, "Assistance" ], @@ -492,7 +501,10 @@ makeAssistanceCheckbox[ ] := "Enable automatic assistance", "If enabled, automatic AI provided suggestions will be added following evaluation results." ] - ]; + ], + "Notebooks", + "Assistance" +]; makeAssistanceCheckbox // endDefinition; @@ -501,7 +513,7 @@ makeAssistanceCheckbox // endDefinition; (*makeTemperatureInput*) makeTemperatureInput // beginDefinition; -makeTemperatureInput[ ] := +makeTemperatureInput[ ] := highlightControl[ prefsInputField[ "Temperature:", Dynamic[ @@ -513,7 +525,10 @@ makeTemperatureInput[ ] := ], Number, ImageSize -> { 50, Automatic } - ]; + ], + "Notebooks", + "Temperature" +]; makeTemperatureInput // endDefinition; @@ -525,10 +540,10 @@ makeInterfaceContent // beginDefinition; makeInterfaceContent[ ] := Enclose[ Module[ { formatCheckbox, includeHistory, chatHistoryLength, mergeMessages }, - formatCheckbox = ConfirmMatch[ makeFormatCheckbox[ ], _Grid|_Row, "FormatCheckbox" ]; - includeHistory = ConfirmMatch[ makeIncludeHistoryCheckbox[ ], _Grid|_Row, "ChatHistory" ]; - chatHistoryLength = ConfirmMatch[ makeChatHistoryLengthInput[ ], _Grid|_Row, "ChatHistoryLength" ]; - mergeMessages = ConfirmMatch[ makeMergeMessagesCheckbox[ ], _Grid|_Row, "MergeMessages" ]; + formatCheckbox = ConfirmMatch[ makeFormatCheckbox[ ] , _Style, "FormatCheckbox" ]; + includeHistory = ConfirmMatch[ makeIncludeHistoryCheckbox[ ], _Style, "ChatHistory" ]; + chatHistoryLength = ConfirmMatch[ makeChatHistoryLengthInput[ ], _Style, "ChatHistoryLength" ]; + mergeMessages = ConfirmMatch[ makeMergeMessagesCheckbox[ ] , _Style, "MergeMessages" ]; Grid[ { @@ -551,14 +566,17 @@ makeInterfaceContent // endDefinition; (*makeFormatCheckbox*) makeFormatCheckbox // beginDefinition; -makeFormatCheckbox[ ] := +makeFormatCheckbox[ ] := highlightControl[ prefsCheckbox[ Dynamic[ TrueQ @ CurrentChatSettings[ $FrontEnd, "AutoFormat" ], (CurrentChatSettings[ $FrontEnd, "AutoFormat" ] = #1) & ], "Format chat output" - ]; + ], + "Notebooks", + "AutoFormat" +]; makeFormatCheckbox // endDefinition; @@ -567,7 +585,7 @@ makeFormatCheckbox // endDefinition; (*makeIncludeHistoryCheckbox*) makeIncludeHistoryCheckbox // beginDefinition; -makeIncludeHistoryCheckbox[ ] := +makeIncludeHistoryCheckbox[ ] := highlightControl[ prefsCheckbox[ Dynamic[ MatchQ[ CurrentChatSettings[ $FrontEnd, "IncludeHistory" ], True|Automatic ], @@ -577,7 +595,10 @@ makeIncludeHistoryCheckbox[ ] := "Include chat history", "If enabled, cells preceding the chat input will be included as additional context for the LLM." ] - ]; + ], + "Notebooks", + "IncludeHistory" +]; makeIncludeHistoryCheckbox // endDefinition; @@ -586,7 +607,7 @@ makeIncludeHistoryCheckbox // endDefinition; (*makeChatHistoryLengthInput*) makeChatHistoryLengthInput // beginDefinition; -makeChatHistoryLengthInput[ ] := +makeChatHistoryLengthInput[ ] := highlightControl[ infoTooltip[ prefsInputField[ "Chat history length:", @@ -601,7 +622,10 @@ makeChatHistoryLengthInput[ ] := ImageSize -> { 50, Automatic } ], "Maximum number of cells to include in chat history" - ]; + ], + "Notebooks", + "ChatHistoryLength" +]; makeChatHistoryLengthInput // endDefinition; @@ -610,7 +634,7 @@ makeChatHistoryLengthInput // endDefinition; (*makeMergeMessagesCheckbox*) makeMergeMessagesCheckbox // beginDefinition; -makeMergeMessagesCheckbox[ ] := +makeMergeMessagesCheckbox[ ] := highlightControl[ prefsCheckbox[ Dynamic[ MatchQ[ CurrentChatSettings[ $FrontEnd, "MergeMessages" ], True|Automatic ], @@ -620,7 +644,10 @@ makeMergeMessagesCheckbox[ ] := "Merge chat messages", "If enabled, adjacent cells with the same author will be merged into a single chat message." ] - ]; + ], + "Notebooks", + "MergeMessages" +]; makeMergeMessagesCheckbox // endDefinition; @@ -632,9 +659,9 @@ makeFeaturesContent // beginDefinition; makeFeaturesContent[ ] := Enclose[ Module[ { multimodal, toolsEnabled, toolFrequency }, - multimodal = ConfirmMatch[ makeMultimodalMenu[ ], _Grid|_Row, "Multimodal" ]; - toolsEnabled = ConfirmMatch[ makeToolsEnabledMenu[ ], _Grid|_Row, "ToolsEnabled" ]; - toolFrequency = ConfirmMatch[ makeToolCallFrequencySelector[ ], _Grid|_Row, "ToolFrequency" ]; + multimodal = ConfirmMatch[ makeMultimodalMenu[ ] , _Style, "Multimodal" ]; + toolsEnabled = ConfirmMatch[ makeToolsEnabledMenu[ ] , _Style, "ToolsEnabled" ]; + toolFrequency = ConfirmMatch[ makeToolCallFrequencySelector[ ], _Style, "ToolFrequency" ]; Grid[ { @@ -656,7 +683,7 @@ makeFeaturesContent // endDefinition; (*makeMultimodalMenu*) makeMultimodalMenu // beginDefinition; -makeMultimodalMenu[ ] := +makeMultimodalMenu[ ] := highlightControl[ Grid[ { { @@ -674,7 +701,10 @@ makeMultimodalMenu[ ] := }, Alignment -> { Left, Baseline }, Spacings -> 0.5 - ]; + ], + "Notebooks", + "Multimodal" +]; makeMultimodalMenu // endDefinition; @@ -683,7 +713,7 @@ makeMultimodalMenu // endDefinition; (*makeToolsEnabledMenu*) makeToolsEnabledMenu // beginDefinition; -makeToolsEnabledMenu[ ] := +makeToolsEnabledMenu[ ] := highlightControl[ Grid[ { { @@ -701,7 +731,10 @@ makeToolsEnabledMenu[ ] := }, Alignment -> { Left, Baseline }, Spacings -> 0.5 - ]; + ], + "Notebooks", + "ToolsEnabled" +]; makeToolsEnabledMenu // endDefinition; @@ -710,7 +743,7 @@ makeToolsEnabledMenu // endDefinition; (*makeToolCallFrequencySelector*) makeToolCallFrequencySelector // beginDefinition; -makeToolCallFrequencySelector[ ] := +makeToolCallFrequencySelector[ ] := highlightControl[ Grid[ { { @@ -720,7 +753,10 @@ makeToolCallFrequencySelector[ ] := }, Alignment -> { Left, Baseline }, Spacings -> 0.5 - ]; + ], + "Notebooks", + "ToolCallFrequency" +]; makeToolCallFrequencySelector // endDefinition; @@ -1176,7 +1212,7 @@ $resetButton = Needs[ "Wolfram`Chatbook`" -> None ]; resetChatPreferences @ CurrentValue[ $FrontEnd, - { PrivateFrontEndOptions, "InterfaceSettings", "Chatbook", "PreferencesTab" } + { PrivateFrontEndOptions, "DialogSettings", "Preferences", "TabSettings", "AI", "Top" } ] , BaseStyle -> { @@ -1231,14 +1267,41 @@ resetChatPreferences // endDefinition; (*openPreferencesPage*) openPreferencesPage // beginDefinition; -openPreferencesPage[ page: $$preferencesPage ] := ( - CurrentValue[ $FrontEnd, { "PreferencesSettings", "Page" } ] = "AI"; - CurrentValue[ $FrontEnd, { PrivateFrontEndOptions, "InterfaceSettings", "Chatbook", "PreferencesTab" } ] = page; - FrontEndTokenExecute[ "PreferencesDialog" ] -); +openPreferencesPage[ page: $$preferencesPage ] := + NotebookTools`OpenPreferencesDialog @ { "AI", page }; + +openPreferencesPage[ page: $$preferencesPage, id_ ] := + NotebookTools`OpenPreferencesDialog[ { "AI", page }, { "AI", page, id } ]; openPreferencesPage // endDefinition; +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*highlightControl*) +highlightControl // beginDefinition; +highlightControl[ expr_, tab_, id_ ] := Style[ expr, Background -> highlightColor[ tab, id ] ]; +highlightControl // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*highlightColor*) +highlightColor // beginDefinition; + +highlightColor[ tab_, id_ ] := + With[ + { + hid := FrontEnd`AbsoluteCurrentValue[ + $FrontEndSession, + { PrivateFrontEndOptions, "DialogSettings", "Preferences", "ControlHighlight", "HighlightID" }, + None + ], + color := FrontEnd`AbsoluteCurrentValue[ EvaluationNotebook[ ], { TaggingRules, "HighlightColor" }, None ] + }, + Dynamic @ If[ hid === { "AI", tab, id }, color, None ] + ]; + +highlightColor // endDefinition; + (* ::**************************************************************************************************************:: *) (* ::Section::Closed:: *) (*Package Footer*) From 2b7b2616f3aa24cbb1b362e8c09773eef897560a Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Mon, 11 Dec 2023 14:07:38 -0500 Subject: [PATCH 27/50] Update formatting of persona manager to fit in preferences --- Source/Chatbook/Dialogs.wl | 19 +++- Source/Chatbook/PersonaManager.wl | 131 ++++++++++++++------------ Source/Chatbook/PreferencesContent.wl | 3 + Source/Chatbook/ToolManager.wl | 37 ++++---- 4 files changed, 105 insertions(+), 85 deletions(-) diff --git a/Source/Chatbook/Dialogs.wl b/Source/Chatbook/Dialogs.wl index 4c38c048..724f7aef 100644 --- a/Source/Chatbook/Dialogs.wl +++ b/Source/Chatbook/Dialogs.wl @@ -32,9 +32,13 @@ Needs[ "Wolfram`Chatbook`ResourceInstaller`" ]; (* ::**************************************************************************************************************:: *) (* ::Section::Closed:: *) (*Configuration*) +$inDialog = False; $dialogHeaderMargins = { { 30, 30 }, { 13, 9 } }; $dialogSubHeaderMargins = { { 30, 30 }, { 0, 9 } }; $dialogBodyMargins = { { 30, 30 }, { 13, 5 } }; +$paneHeaderMargins = { { 5, 30 }, { 13, 9 } }; +$paneSubHeaderMargins = { { 5, 30 }, { 0, 9 } }; +$paneBodyMargins = { { 5, 30 }, { 13, 5 } }; $baseStyle := $baseStyles[ "Default" ]; $baseStyles = <| @@ -42,6 +46,10 @@ $baseStyles = <| "DialogSubHeader" -> { FontSize -> 14, FontWeight -> "DemiBold" } |>; +$headerMargins := If[ TrueQ @ $inDialog, $dialogHeaderMargins , $paneHeaderMargins ]; +$subHeaderMargins := If[ TrueQ @ $inDialog, $dialogSubHeaderMargins, $paneSubHeaderMargins ]; +$bodyMargins := If[ TrueQ @ $inDialog, $dialogBodyMargins , $paneBodyMargins ]; + (* ::**************************************************************************************************************:: *) (* ::Section::Closed:: *) (*Create Dialogs*) @@ -139,11 +147,12 @@ dialogPane // beginDefinition; dialogPane[ expr_ ] := dialogPane[ expr, "DialogBody" ]; dialogPane[ expr_, style_ ] := dialogPane[ expr, style, Automatic ]; +dialogPane[ expr_, style_, margins_ ] := dialogPane[ expr, style, margins, $inDialog ]; -dialogPane[ exprs_List, style_, margins_ ] := dialogPane[ exprs, style, margins ] = +dialogPane[ exprs_List, style_, margins_, inDialog_ ] := dialogPane[ exprs, style, margins, inDialog ] = dialogPane0[ #, style, margins ] & /@ exprs; -dialogPane[ expr_, style_, margins_ ] := dialogPane[ expr, style, margins ] = +dialogPane[ expr_, style_, margins_, inDialog_ ] := dialogPane[ expr, style, margins, inDialog ] = { dialogPane0[ expr, style, margins ], SpanFromLeft }; dialogPane // endDefinition; @@ -173,9 +182,9 @@ dialogBaseStyle // endDefinition; (* ::Subsubsection::Closed:: *) (*dialogMargins*) dialogMargins // beginDefinition; -dialogMargins[ "DialogBody" , margins_ ] := autoMargins[ margins, $dialogBodyMargins ]; -dialogMargins[ "DialogHeader" , margins_ ] := autoMargins[ margins, $dialogHeaderMargins ]; -dialogMargins[ "DialogSubHeader", margins_ ] := autoMargins[ margins, $dialogSubHeaderMargins ]; +dialogMargins[ "DialogBody" , margins_ ] := autoMargins[ margins, $bodyMargins ]; +dialogMargins[ "DialogHeader" , margins_ ] := autoMargins[ margins, $headerMargins ]; +dialogMargins[ "DialogSubHeader", margins_ ] := autoMargins[ margins, $subHeaderMargins ]; dialogMargins[ _ , margins_ ] := margins; dialogMargins // endDefinition; diff --git a/Source/Chatbook/PersonaManager.wl b/Source/Chatbook/PersonaManager.wl index 3f1796f6..a07e0d40 100644 --- a/Source/Chatbook/PersonaManager.wl +++ b/Source/Chatbook/PersonaManager.wl @@ -47,54 +47,36 @@ CreatePersonaManagerPanel[ ] := DynamicModule[{favorites, delimColor}, Framed[ Grid[ { - { - Pane[ - Style["Add & Manage Personas", "DialogHeader"], - FrameMargins -> Dynamic[CurrentValue[{StyleDefinitions, "DialogHeader", CellMargins}]], - ImageSize -> {501, Automatic}]}, - { - Pane[ - Dynamic[ - StringTemplate["`n1` personas being shown in the prompt menu. `n2` total personas available."][ - <| - "n1" -> If[ListQ[#], Length[#], "\[LongDash]"]&[CurrentValue[$FrontEnd, {PrivateFrontEndOptions, "InterfaceSettings", "Chatbook", "VisiblePersonas"}]], - "n2" -> If[Length[#] > 0, Length[#], "\[LongDash]"]&[$CachedPersonaData]|>], - TrackedSymbols :> {$CachedPersonaData}], - BaseStyle -> "DialogBody", - FrameMargins -> Dynamic[Replace[CurrentValue[{StyleDefinitions, "DialogBody", CellMargins}], {{l_, r_}, {b_, t_}} :> {{l, r}, {0, t}}]]]}, - { - Pane[ - Grid[{{ + If[ TrueQ @ $inDialog, dialogHeader[ "Add & Manage Personas" ], Nothing ], + + (* ----- Install Personas ----- *) + dialogSubHeader[ "Install Personas" ], + dialogBody[ + Grid @ { + { "Install from", Button[ - NotebookTools`Mousedown[ - Framed["Prompt Repository", BaseStyle -> "ButtonGray1Normal", BaselinePosition -> Baseline], - Framed["Prompt Repository", BaseStyle -> "ButtonGray1Hover", BaselinePosition -> Baseline], - Framed["Prompt Repository", BaseStyle -> "ButtonGray1Pressed", BaselinePosition -> Baseline], - BaseStyle -> "DialogTextBasic"], + grayDialogButtonLabel[ "Prompt Repository \[UpperRightArrow]" ], ResourceInstallFromRepository[ "Prompt" ], - Appearance -> "Suppressed", BaselinePosition -> Baseline, Method -> "Queued"], + Appearance -> "Suppressed", + BaselinePosition -> Baseline, + Method -> "Queued" + ], Button[ - NotebookTools`Mousedown[ - Framed["URL", BaseStyle -> "ButtonGray1Normal", BaselinePosition -> Baseline], - Framed["URL", BaseStyle -> "ButtonGray1Hover", BaselinePosition -> Baseline], - Framed["URL", BaseStyle -> "ButtonGray1Pressed", BaselinePosition -> Baseline], - BaseStyle -> "DialogTextBasic"], + grayDialogButtonLabel[ "URL" ], Block[ { PrintTemporary }, ResourceInstallFromURL[ "Prompt" ] ], - Appearance -> "Suppressed", BaselinePosition -> Baseline, Method -> "Queued"](* , - (* FIXME: FUTURE *) - Button[ - NotebookTools`Mousedown[ - Framed["File", BaseStyle -> "ButtonGray1Normal", BaselinePosition -> Baseline], - Framed["File", BaseStyle -> "ButtonGray1Hover", BaselinePosition -> Baseline], - Framed["File", BaseStyle -> "ButtonGray1Pressed", BaselinePosition -> Baseline], - BaseStyle -> "DialogTextBasic"], - If[AssociationQ[PersonaInstallFromFile[]], GetPersonaData[]], - Appearance -> "Suppressed", BaselinePosition -> Baseline, Method -> "Queued"] *)}}], - BaseStyle -> "DialogBody", - FrameMargins -> Dynamic[Replace[CurrentValue[{StyleDefinitions, "DialogBody", CellMargins}], {{l_, r_}, {b_, t_}} :> {{l, r}, {15, 5}}]]]}, + Appearance -> "Suppressed", + BaselinePosition -> Baseline, + Method -> "Queued" + ] + } + } + ], + + (* ----- Configure and Enable Personas ----- *) + dialogSubHeader[ "Manage and Enable Personas", { Automatic, { 5, Automatic } } ], { - Pane[#, AppearanceElements -> None, ImageSize -> {Full, UpTo[300]}, Scrollbars -> {False, Automatic}]& @ + If[ $inDialog, Pane[#, AppearanceElements -> None, ImageSize -> {Full, UpTo[300]}, Scrollbars -> {False, Automatic}], # ]& @ Dynamic[ Grid[ Prepend[ @@ -113,35 +95,60 @@ CreatePersonaManagerPanel[ ] := DynamicModule[{favorites, delimColor}, {{True}}, { 2 -> False, - Length[favorites] + 2 -> Directive[delimColor, AbsoluteThickness[5]]}}}, + Length[favorites] + 2 -> Directive[delimColor, AbsoluteThickness[5]] + } + } + }, FrameStyle -> Dynamic[delimColor], ItemSize -> {{Automatic, Automatic, Automatic, Automatic, Fit, {Automatic}}, {}}, Spacings -> { {{{1}}, {2 -> 1, 4 -> 0.5}}, - 0.5}], - TrackedSymbols :> {$CachedPersonaData}]}, - { - Item[ - Button[(* give Default properties using specific FEExpression *) - NotebookTools`Mousedown[ - Framed["OK", BaseStyle -> "ButtonRed1Normal", BaselinePosition -> Baseline], - Framed["OK", BaseStyle -> "ButtonRed1Hover", BaselinePosition -> Baseline], - Framed["OK", BaseStyle -> "ButtonRed1Pressed", BaselinePosition -> Baseline], - BaseStyle -> "DialogTextBasic"], - DialogReturn @ channelCleanup[ ], - Appearance -> FEPrivate`FrontEndResource["FEExpressions", "DefaultSuppressMouseDownNinePatchAppearance"], - ImageMargins -> {{0, 31}, {14, 14}}, - ImageSize -> Automatic ], - Alignment -> {Right, Center}]}}, + {{{0.5}}, {Length[favorites] + 2 -> 1}} + } + ], + TrackedSymbols :> {$CachedPersonaData} + ] + }, + + (* ----- Dialog Buttons ----- *) + If[ TrueQ @ $inDialog, + { + Item[ + Button[(* give Default properties using specific FEExpression *) + redDialogButtonLabel[ "OK" ], + DialogReturn @ channelCleanup[ ], + Appearance -> FEPrivate`FrontEndResource["FEExpressions", "DefaultSuppressMouseDownNinePatchAppearance"], + ImageMargins -> {{0, 31}, {14, 14}}, + ImageSize -> Automatic + ], + Alignment -> {Right, Center} + ] + }, + { "" } + ] + }, Alignment -> Left, - BaseStyle -> {FontSize -> 1}, (* useful setting in case we want fixed-width columns; ItemSize would scale at the same rate as ImageSize *) - Dividers -> {{}, {2 -> True, 4 -> Directive[delimColor, AbsoluteThickness[5]], -2 -> Directive[delimColor, AbsoluteThickness[5]]}}, + BaseStyle -> $baseStyle, (* useful setting in case we want fixed-width columns; ItemSize would scale at the same rate as ImageSize *) + Dividers -> { + {}, + If[ TrueQ @ $inDialog, + { + 2 -> True, + 4 -> True, + -2 -> Directive[delimColor, AbsoluteThickness[5]] + }, + { + 3 -> True + } + ] + }, FrameStyle -> Dynamic[delimColor], - Spacings -> {0, 0}], + Spacings -> {0, 0} + ], ContentPadding -> 0, FrameMargins -> -1, FrameStyle -> None, - ImageSize -> {501, All}], + ImageSize -> { If[ TrueQ @ $inDialog, 501, Automatic ], All}], Initialization :> ( delimColor = CurrentValue[{StyleDefinitions, "DialogDelimiter", CellFrameColor}]; GetPersonaData[]; (* sets $CachedPersonaData *) diff --git a/Source/Chatbook/PreferencesContent.wl b/Source/Chatbook/PreferencesContent.wl index baf5c79c..d28d51ef 100644 --- a/Source/Chatbook/PreferencesContent.wl +++ b/Source/Chatbook/PreferencesContent.wl @@ -1267,6 +1267,9 @@ resetChatPreferences // endDefinition; (*openPreferencesPage*) openPreferencesPage // beginDefinition; +openPreferencesPage[ ] := + openPreferencesPage[ "Notebooks" ]; + openPreferencesPage[ page: $$preferencesPage ] := NotebookTools`OpenPreferencesDialog @ { "AI", page }; diff --git a/Source/Chatbook/ToolManager.wl b/Source/Chatbook/ToolManager.wl index 2904dc3a..e8de9d2d 100644 --- a/Source/Chatbook/ToolManager.wl +++ b/Source/Chatbook/ToolManager.wl @@ -65,7 +65,7 @@ CreateLLMToolManagerPanel[ tools0_List, personas_List ] := { globalTools, personaTools, personaToolNames, personaToolLookup, tools, preppedPersonas, preppedTools, personaNames, personaDisplayNames, - toolNames, toolDefaultPersonas, gridOpts, marginL, marginH, margins + toolNames, toolDefaultPersonas, gridOpts }, globalTools = toolName @ tools0; @@ -133,19 +133,13 @@ CreateLLMToolManagerPanel[ tools0_List, personas_List ] := ] ]; - marginL = If[ TrueQ @ $inDialog, Automatic, 5 ]; - marginH = { marginL, Automatic }; - margins = { marginH, Automatic }; - DynamicWrapper[ Grid[ { - (* ----- Install Tools ----- *) If[ TrueQ @ $inDialog, dialogHeader[ "Add & Manage LLM Tools" ], Nothing ], - dialogSubHeader[ - "Install Tools", - margins - ], + + (* ----- Install Tools ----- *) + dialogSubHeader[ "Install Tools" ], dialogBody[ Grid @ { { @@ -165,14 +159,11 @@ CreateLLMToolManagerPanel[ tools0_List, personas_List ] := Method -> "Queued" ] } - }, - margins + } ], (* ----- Configure and Enable Tools ----- *) - - - dialogSubHeader[ "Manage and Enable Tools", margins ], + dialogSubHeader[ "Manage and Enable Tools" ], dialogBody[ Grid @ { { @@ -181,7 +172,7 @@ CreateLLMToolManagerPanel[ tools0_List, personas_List ] := Dynamic @ catchAlways @ toolModelWarning @ scopeMode[ ] } }, - { marginH, { 5, Automatic } } + { Automatic, { 5, Automatic } } ], dialogBody[ EventHandler[ @@ -346,8 +337,9 @@ CreateLLMToolManagerPanel[ tools0_List, personas_List ] := ], { "MouseExited" :> FEPrivate`Set[ { row, column }, { None, None } ] }, PassEventsDown -> True - ], { { marginL, 0 }, Automatic } ], + ], { { Automatic, 0 }, Automatic } ], + (* ----- Dialog Buttons ----- *) If[ TrueQ @ $inDialog, { Item[ @@ -372,7 +364,16 @@ CreateLLMToolManagerPanel[ tools0_List, personas_List ] := }, Alignment -> { Left, Top }, BaseStyle -> $baseStyle, - Dividers -> { False, { False, $dividerCol, False, $dividerCol, False, { False } } }, + Dividers -> { + False, + { + If[ TrueQ @ $inDialog, Sequence @@ { False, $dividerCol }, False ], + False, + $dividerCol, + False, + { False } + } + }, ItemSize -> { Automatic, 0 }, Spacings -> { 0, 0 } ], From f82089d946493af79b84c21345db4d05ecaa1816 Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Mon, 11 Dec 2023 16:13:41 -0500 Subject: [PATCH 28/50] Consistent background for persona panel --- Source/Chatbook/PersonaManager.wl | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Source/Chatbook/PersonaManager.wl b/Source/Chatbook/PersonaManager.wl index a07e0d40..943a819a 100644 --- a/Source/Chatbook/PersonaManager.wl +++ b/Source/Chatbook/PersonaManager.wl @@ -87,7 +87,7 @@ CreatePersonaManagerPanel[ ] := DynamicModule[{favorites, delimColor}, KeySort[$CachedPersonaData]]], {"", "In Menu", "", "Name", ""(*FITME*), (*"Description",*) "Version", ""}], Alignment -> {{Center, Center, {Left}}, Center}, - Background -> {{}, {RGBColor["#e5e5e5"]}}, + Background -> {{}, {RGBColor["#e5e5e5"], {White}}}, BaseStyle -> "DialogBody", Dividers -> Dynamic @ { {}, From 9c658aefd230365848c7ab9eb4284ec02cebad61 Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Mon, 11 Dec 2023 16:14:06 -0500 Subject: [PATCH 29/50] Validate "ChatHistoryLength" value --- Source/Chatbook/PreferencesContent.wl | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/Source/Chatbook/PreferencesContent.wl b/Source/Chatbook/PreferencesContent.wl index d28d51ef..ffe772d5 100644 --- a/Source/Chatbook/PreferencesContent.wl +++ b/Source/Chatbook/PreferencesContent.wl @@ -615,7 +615,9 @@ makeChatHistoryLengthInput[ ] := highlightControl[ CurrentChatSettings[ $FrontEnd, "ChatHistoryLength" ], { None, - If[ NumberQ @ #, CurrentChatSettings[ $FrontEnd, "ChatHistoryLength" ] = Floor[ # ] ] & + If[ NumberQ @ # && NonNegative @ #, + CurrentChatSettings[ $FrontEnd, "ChatHistoryLength" ] = Floor[ # ] + ] & } ], Number, From eed8c084237ea2548cf3a240a505bf09d5f0c466 Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Mon, 11 Dec 2023 16:14:43 -0500 Subject: [PATCH 30/50] Horizontal layout for tool call frequency slider --- Source/Chatbook/PreferencesContent.wl | 88 +++++++++++++++++++++++---- 1 file changed, 75 insertions(+), 13 deletions(-) diff --git a/Source/Chatbook/PreferencesContent.wl b/Source/Chatbook/PreferencesContent.wl index ffe772d5..2149d001 100644 --- a/Source/Chatbook/PreferencesContent.wl +++ b/Source/Chatbook/PreferencesContent.wl @@ -105,8 +105,7 @@ preferencesContent[ "Notebooks" ] := trackedDynamic[ notebookSettingsPanel[ ], { preferencesContent[ "Personas" ] := trackedDynamic[ personaSettingsPanel[ ], { "Personas" } ]; (* Content for the "Services" tab: *) -(* FIXME: this is placeholder code *) -preferencesContent[ "Services" ] := trackedDynamic[ "Coming soon.", { "Models" } ]; +preferencesContent[ "Services" ] := trackedDynamic[ servicesSettingsPanel[ ], { "Models" } ]; (* Content for the "Tools" tab: *) preferencesContent[ "Tools" ] := toolSettingsPanel[ ]; @@ -731,8 +730,9 @@ makeToolsEnabledMenu[ ] := highlightControl[ ] } }, - Alignment -> { Left, Baseline }, - Spacings -> 0.5 + Alignment -> { Left, Baseline }, + BaselinePosition -> 1, + Spacings -> 0.5 ], "Notebooks", "ToolsEnabled" @@ -746,15 +746,71 @@ makeToolsEnabledMenu // endDefinition; makeToolCallFrequencySelector // beginDefinition; makeToolCallFrequencySelector[ ] := highlightControl[ - Grid[ - { + DynamicModule[ { type, frequency }, + Grid[ { - Style[ "Tool call frequency:", "leadinText" ], - makeToolCallFrequencySlider[ $FrontEnd ] - } - }, - Alignment -> { Left, Baseline }, - Spacings -> 0.5 + { + Style[ "Tool call frequency:", "leadinText" ], + PopupMenu[ + Dynamic[ + type, + Function[ + If[ # === Automatic + , + type = Automatic; + CurrentChatSettings[ $FrontEnd, "ToolCallFrequency" ] = Automatic + , + type = "Custom"; + CurrentChatSettings[ $FrontEnd, "ToolCallFrequency" ] = 0.5 + ] + ] + ], + { + Automatic -> "Automatic", + "Custom" -> "Custom" + }, + MenuStyle -> "controlText" + ], + PaneSelector[ + { + Automatic -> "", + "Custom" -> Grid[ + { + { + Spacer[ 5 ], + Style[ "Rare", "defaultSubtext" ], + Slider[ + Dynamic[ + frequency, + { + Function[ frequency = # ], + Function[ + CurrentChatSettings[ $FrontEnd, "ToolCallFrequency" ] = #; + frequency = # + ] + } + ], + ImageSize -> { 100, Automatic } + ], + Style[ "Often", "defaultSubtext" ] + } + }, + Spacings -> { 0.4, 0.7 } + ] + }, + Dynamic[ type ], + ImageSize -> Automatic + ] + } + }, + Alignment -> { Left, Baseline }, + BaselinePosition -> 1, + Spacings -> 0.5 + ], + Initialization :> With[ { val = CurrentChatSettings[ $FrontEnd, "ToolCallFrequency" ] }, + type = If[ NumberQ @ val, "Custom", Automatic ]; + frequency = If[ NumberQ @ val, val, 0.5 ]; + ] ], "Notebooks", "ToolCallFrequency" @@ -765,7 +821,13 @@ makeToolCallFrequencySelector // endDefinition; (* ::**************************************************************************************************************:: *) (* ::Section::Closed:: *) (*Services*) -(* TODO *) + +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*servicesSettingsPanel*) +servicesSettingsPanel // beginDefinition; +servicesSettingsPanel[ ] := "Test text, please ignore"; +servicesSettingsPanel // endDefinition; (* ::**************************************************************************************************************:: *) (* ::Section::Closed:: *) From 30329e1dadff2654dfe041c3f9a520b7ef829cf7 Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Wed, 13 Dec 2023 10:42:37 -0500 Subject: [PATCH 31/50] Added services panel to preferences --- Source/Chatbook/Dynamics.wl | 1 + Source/Chatbook/PreferencesContent.wl | 608 +++++++++++++++++--------- Source/Chatbook/Services.wl | 51 ++- 3 files changed, 446 insertions(+), 214 deletions(-) diff --git a/Source/Chatbook/Dynamics.wl b/Source/Chatbook/Dynamics.wl index 08211606..899a382a 100644 --- a/Source/Chatbook/Dynamics.wl +++ b/Source/Chatbook/Dynamics.wl @@ -21,6 +21,7 @@ $dynamicTriggers = <| "Models" :> $modelsTrigger, "Personas" :> $personasTrigger, "Preferences" :> $preferencesTrigger, + "Services" :> $servicesTrigger, "Tools" :> $toolsTrigger |>; diff --git a/Source/Chatbook/PreferencesContent.wl b/Source/Chatbook/PreferencesContent.wl index 2149d001..eda9a962 100644 --- a/Source/Chatbook/PreferencesContent.wl +++ b/Source/Chatbook/PreferencesContent.wl @@ -105,7 +105,7 @@ preferencesContent[ "Notebooks" ] := trackedDynamic[ notebookSettingsPanel[ ], { preferencesContent[ "Personas" ] := trackedDynamic[ personaSettingsPanel[ ], { "Personas" } ]; (* Content for the "Services" tab: *) -preferencesContent[ "Services" ] := trackedDynamic[ servicesSettingsPanel[ ], { "Models" } ]; +preferencesContent[ "Services" ] := trackedDynamic[ servicesSettingsPanel[ ], { "Models", "Services" } ]; (* Content for the "Tools" tab: *) preferencesContent[ "Tools" ] := toolSettingsPanel[ ]; @@ -216,22 +216,22 @@ createNotebookSettingsPanel // endDefinition; makeDefaultSettingsContent // beginDefinition; makeDefaultSettingsContent[ ] := Enclose[ - Module[ { personaSelector, modelSelector, assistanceCheckbox, temperatureInput }, + Module[ { assistanceCheckbox, personaSelector, modelSelector, temperatureInput }, + (* Checkbox to enable automatic assistance for normal shift-enter evaluations: *) + assistanceCheckbox = ConfirmMatch[ makeAssistanceCheckbox[ ], _Style, "AssistanceCheckbox" ]; (* The personaSelector is a pop-up menu for selecting the default persona: *) personaSelector = ConfirmMatch[ makePersonaSelector[ ], _Style, "PersonaSelector" ]; (* The modelSelector is a dynamic module containing menus to select the service and model separately: *) modelSelector = ConfirmMatch[ makeModelSelector[ ], _DynamicModule, "ModelSelector" ]; - (* Checkbox to enable automatic assistance for normal shift-enter evaluations: *) - assistanceCheckbox = ConfirmMatch[ makeAssistanceCheckbox[ ], _Style, "AssistanceCheckbox" ]; (* The temperatureInput is an input field for setting the default 'temperature' for responses: *) temperatureInput = ConfirmMatch[ makeTemperatureInput[ ], _Style, "TemperatureInput" ]; (* Assemble the persona selector, model selector, and temperature slider into a grid layout: *) Grid[ { + { assistanceCheckbox }, { personaSelector }, { modelSelector }, - { assistanceCheckbox }, { temperatureInput } }, Alignment -> { Left, Baseline }, @@ -273,7 +273,7 @@ makePersonaSelector[ personas: { (_String -> _).. } ] := ] }, "Notebooks", - "DefaultPersona" + "LLMEvaluator" ]; makePersonaSelector // endDefinition; @@ -308,7 +308,12 @@ makeModelSelector[ services_Association? AssociationQ ] := Enclose[ state = If[ modelListCachedQ @ service, "Loaded", "Loading" ]; modelSelector = If[ state === "Loaded", - makeModelNameSelector[ Dynamic @ service, Dynamic @ model ], + makeModelNameSelector[ + Dynamic @ service, + Dynamic @ model, + Dynamic @ modelSelector, + Dynamic @ state + ], "" ]; @@ -322,21 +327,30 @@ makeModelSelector[ services_Association? AssociationQ ] := Enclose[ highlight = highlightControl[ Row @ { #1, Spacer[ 1 ], #2 }, "Notebooks", #3 ] &; - Row @ { - highlight[ "Default LLM Service:", serviceSelector, "DefaultService" ], - Spacer[ 5 ], - highlight[ - "Default Model:", - Dynamic[ - If[ state === "Loading", $loadingPopupMenu, modelSelector ], - TrackedSymbols :> { state, modelSelector } - ], - "DefaultModel" - ] - }, + highlightControl[ + Row @ { + highlight[ "Default LLM Service:", serviceSelector, "ModelService" ], + Spacer[ 5 ], + highlight[ + "Default Model:", + Dynamic[ + If[ state === "Loading", $loadingPopupMenu, modelSelector ], + TrackedSymbols :> { state, modelSelector } + ], + "ModelName" + ] + }, + "Notebooks", + "Model" + ], Initialization :> ( - modelSelector = catchAlways @ makeModelNameSelector[ Dynamic @ service, Dynamic @ model ]; + modelSelector = catchAlways @ makeModelNameSelector[ + Dynamic @ service, + Dynamic @ model, + Dynamic @ modelSelector, + Dynamic @ state + ]; state = "Loaded"; ), SynchronousInitialization -> False, @@ -400,10 +414,20 @@ serviceSelectCallback[ (* Finish loading the model name selector: *) If[ state === "Loading", SessionSubmit[ - modelSelector = makeModelNameSelector[ Dynamic @ service, Dynamic @ model ]; + modelSelector = makeModelNameSelector[ + Dynamic @ service, + Dynamic @ model, + Dynamic @ modelSelector, + Dynamic @ state + ]; state = "Loaded" ], - modelSelector = makeModelNameSelector[ Dynamic @ service, Dynamic @ model ] + modelSelector = makeModelNameSelector[ + Dynamic @ service, + Dynamic @ model, + Dynamic @ modelSelector, + Dynamic @ state + ] ] ]; @@ -414,13 +438,41 @@ serviceSelectCallback // endDefinition; (*makeModelNameSelector*) makeModelNameSelector // beginDefinition; -makeModelNameSelector[ Dynamic[ service_ ], Dynamic[ model_ ] ] := Enclose[ - Module[ { models, current, default, fallback }, +makeModelNameSelector[ + Dynamic[ service_ ], + Dynamic[ model_ ], + Dynamic[ modelSelector_ ], + Dynamic[ state_ ] +] := Enclose[ + Catch @ Module[ { models, current, default, fallback }, ensureServiceName @ service; ConfirmAssert[ StringQ @ service, "ServiceName" ]; - models = ConfirmMatch[ getServiceModelList @ service, { __Association }, "ServiceModelList" ]; + models = ConfirmMatch[ + Block[ { $allowConnectionDialog = False }, getServiceModelList @ service ], + { __Association } | Missing[ "NotConnected" ] | Missing[ "NoModelList" ], + "ServiceModelList" + ]; + + If[ models === Missing[ "NotConnected" ], + Throw @ serviceConnectButton[ + Dynamic @ service, + Dynamic @ model, + Dynamic @ modelSelector, + Dynamic @ state + ] + ]; + + If[ models === Missing[ "NoModelList" ], + Throw @ modelNameInputField[ + Dynamic @ service, + Dynamic @ model, + Dynamic @ modelSelector, + Dynamic @ state + ] + ]; + current = extractModelName @ CurrentChatSettings[ $FrontEnd, "Model" ]; default = ConfirmBy[ getServiceDefaultModel @ service, StringQ, "DefaultName" ]; fallback = <| "Service" -> service, "Name" -> default |>; @@ -452,6 +504,60 @@ makeModelNameSelector[ Dynamic[ service_ ], Dynamic[ model_ ] ] := Enclose[ makeModelNameSelector // endDefinition; +(* ::**************************************************************************************************************:: *) +(* ::Subsubsubsection::Closed:: *) +(*modelNameInputField*) +modelNameInputField // beginDefinition; + +modelNameInputField[ Dynamic[ service_ ], Dynamic[ model_ ], Dynamic[ modelSelector_ ], Dynamic[ state_ ] ] := + prefsInputField[ + "Model:", + Dynamic[ + Replace[ + extractModelName @ CurrentChatSettings[ $FrontEnd, "Model" ], + Except[ _String ] :> "" + ], + { None, modelSelectCallback[ Dynamic @ service, Dynamic @ model ] } + ], + String, + ImageSize -> { 200, Automatic } + ]; + +modelNameInputField // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsubsection::Closed:: *) +(*serviceConnectButton*) +serviceConnectButton // beginDefinition; + +serviceConnectButton[ + Dynamic[ service_ ], + Dynamic[ model_ ], + Dynamic[ modelSelector_ ], + Dynamic[ state_ ] +] := + Button[ + "Connect for model list", + Needs[ "Wolfram`LLMFunctions`" -> None ]; + Replace[ + (* cSpell: ignore genconerr *) + Quiet[ Wolfram`LLMFunctions`APIs`Common`ConnectToService @ service, { ServiceConnect::genconerr } ], + _ServiceObject :> + If[ ListQ @ getServiceModelList @ service, + serviceSelectCallback[ + service, + Dynamic @ service, + Dynamic @ model, + Dynamic @ modelSelector, + Dynamic @ state + ] + ] + ], + Method -> "Queued" + ]; + +serviceConnectButton // endDefinition; + (* ::**************************************************************************************************************:: *) (* ::Subsubsubsubsection::Closed:: *) (*modelSelectCallback*) @@ -826,9 +932,180 @@ makeToolCallFrequencySelector // endDefinition; (* ::Subsection::Closed:: *) (*servicesSettingsPanel*) servicesSettingsPanel // beginDefinition; -servicesSettingsPanel[ ] := "Test text, please ignore"; + +servicesSettingsPanel[ ] := Enclose[ + Module[ { settingsLabel, settings, serviceGrid }, + + settingsLabel = Style[ "Registered Services", "subsectionText" ]; + settings = ConfirmMatch[ makeModelSelector[ ], _DynamicModule, "ServicesSettings" ]; + serviceGrid = ConfirmMatch[ makeServiceGrid[ ], _Grid, "ServiceGrid" ]; + + Pane[ + Grid[ + { + { settingsLabel }, + { settings }, + { serviceGrid } + }, + Alignment -> { Left, Baseline }, + ItemSize -> { Fit, Automatic }, + Spacings -> { 0, 0.7 } + ], + ImageMargins -> 8 + ] + ], + throwInternalFailure +]; + servicesSettingsPanel // endDefinition; +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*makeServiceGrid*) +makeServiceGrid // beginDefinition; + +makeServiceGrid[ ] := Grid[ + Join[ + { { Spacer[ 1 ], "Service", SpanFromLeft, "Authentication", "", Spacer[ 1 ] } }, + KeyValueMap[ makeServiceGridRow, $availableServices ] + ], + Alignment -> { Left, Baseline }, + Background -> { { }, { GrayLevel[ 0.898 ], { White } } }, + ItemSize -> { { Automatic, Automatic, Scaled[ .3 ], Fit, Automatic }, Automatic }, + Dividers -> { True, All }, + FrameStyle -> GrayLevel[ 0.898 ], + Spacings -> { Automatic, 0.7 } +]; + +makeServiceGrid // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*makeServiceGridRow*) +makeServiceGridRow // beginDefinition; + +makeServiceGridRow[ name_String, data_Association ] := { + Spacer[ 1 ], + resizeMenuIcon @ inlineTemplateBoxes @ serviceIcon @ data, + name, + makeServiceAuthenticationDisplay @ name, + deleteServiceButton @ name, + Spacer[ 1 ] +}; + +makeServiceGridRow // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*deleteServiceButton*) +deleteServiceButton // beginDefinition; + +deleteServiceButton[ "OpenAI" ] := Framed[ + Button[ + Insert[ chatbookIcon[ "ToolManagerBin", False ], GrayLevel[ 0.8 ], { 1, 1, 1 } ], + Null, + Enabled -> False, + $deleteServiceButtonOptions + ], + $deleteServiceButtonFrameOptions +]; + +deleteServiceButton[ service_String ] := Tooltip[ + Framed[ + Button[ + $trashBin, + Needs[ "LLMServices`" -> None ]; + LLMServices`UnregisterService @ service; + disconnectService @ service; + updateDynamics[ { "Services", "Preferences" } ], + $deleteServiceButtonOptions + ], + $deleteServiceButtonFrameOptions + ], + "Unregister service connection" +]; + +deleteServiceButton // endDefinition; + + +$deleteServiceButtonOptions = Sequence[ + Appearance -> "Suppressed", + ContentPadding -> False, + FrameMargins -> 0, + ImageMargins -> 0, + Method -> "Queued" +]; + + +$deleteServiceButtonFrameOptions = Sequence[ + ContentPadding -> False, + FrameMargins -> 0, + FrameStyle -> Transparent, + ImageMargins -> 0 +]; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*makeServiceAuthenticationDisplay*) +makeServiceAuthenticationDisplay // beginDefinition; + +makeServiceAuthenticationDisplay[ service_String ] := + DynamicModule[ { display }, + display = ProgressIndicator[ Appearance -> "Percolate" ]; + Dynamic[ display, TrackedSymbols :> { display } ], + Initialization :> createServiceAuthenticationDisplay[ service, Dynamic[ display ] ], + SynchronousInitialization -> False + ]; + +makeServiceAuthenticationDisplay // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsubsubsection::Closed:: *) +(*createServiceAuthenticationDisplay*) +createServiceAuthenticationDisplay // beginDefinition; + +createServiceAuthenticationDisplay[ service_, Dynamic[ display_ ] ] := Enclose[ + Module[ { type }, + type = ConfirmBy[ credentialType @ service, StringQ, "CredentialType" ]; + display = Row[ + { + Pane[ type, ImageSize -> { 120, Automatic } ], + connectOrDisconnectButton[ service, type, Dynamic @ display ] + }, + Alignment -> { Left, Baseline } + ]; + ], + throwInternalFailure +]; + +createServiceAuthenticationDisplay // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsubsubsection::Closed:: *) +(*connectOrDisconnectButton*) +connectOrDisconnectButton // beginDefinition; + +connectOrDisconnectButton[ service_String, "None", Dynamic[ display_ ] ] := + Button[ + "Connect", + display = ProgressIndicator[ Appearance -> "Percolate" ]; + clearConnectionCache[ service, False ]; + Quiet[ Wolfram`LLMFunctions`APIs`Common`ConnectToService @ service, { ServiceConnect::genconerr } ]; + createServiceAuthenticationDisplay[ service, Dynamic @ display ], + Method -> "Queued" + ]; + +connectOrDisconnectButton[ service_String, "SystemCredential"|"Environment"|"ServiceConnect", Dynamic[ display_ ] ] := + Button[ + "Disconnect", + display = ProgressIndicator[ Appearance -> "Percolate" ]; + disconnectService @ service; + createServiceAuthenticationDisplay[ service, Dynamic @ display ], + Method -> "Queued" + ]; + +connectOrDisconnectButton // endDefinition; + (* ::**************************************************************************************************************:: *) (* ::Section::Closed:: *) (*Personas*) @@ -1047,197 +1324,105 @@ chooseDefaultModelName[ service_ ] := Automatic; chooseDefaultModelName // endDefinition; (* ::**************************************************************************************************************:: *) -(* ::Subsubsection::Closed:: *) -(*makeFrontEndAndNotebookSettingsContent*) -makeFrontEndAndNotebookSettingsContent // beginDefinition; - -makeFrontEndAndNotebookSettingsContent[ - targetObj : _FrontEndObject | $FrontEndSession | _NotebookObject -] := Module[{ - personas = GetPersonasAssociation[], - defaultPersonaPopupItems, - setModelPopupItems, - modelPopupItems -}, - defaultPersonaPopupItems = KeyValueMap[ - {persona, personaSettings} |-> ( - persona -> Row[{ - resizeMenuIcon[ - getPersonaMenuIcon[personaSettings, "Full"] - ], - personaDisplayName[persona, personaSettings] - }, Spacer[1]] - ), - personas - ]; +(* ::Section::Closed:: *) +(*ServiceConnection Utilities*) - (*----------------------------*) - (* Compute the models to show *) - (*----------------------------*) - - setModelPopupItems[] := ( - modelPopupItems = KeyValueMap[ - {modelName, settings} |-> ( - modelName -> Row[{ - getModelMenuIcon[settings, "Full"], - modelDisplayName[modelName] - }, Spacer[1]] - ), - Association[#Name -> # & /@ getServiceModelList["OpenAI"]] +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*disconnectService*) +disconnectService // beginDefinition; + +disconnectService[ service_String ] := + With[ { key = credentialKey @ service }, + Unset @ SystemCredential @ key; + SetEnvironment[ key -> None ]; + clearConnectionCache @ service; + If[ extractServiceName @ CurrentChatSettings[ $FrontEnd, "Model" ] === service, + CurrentChatSettings[ $FrontEnd, "Model" ] = $DefaultModel ]; - ); + updateDynamics[ "Services" ] + ]; - (* Initial value. Called again if 'show snapshot models' changes. *) - setModelPopupItems[]; +disconnectService // endDefinition; - (*---------------------------------*) - (* Return the toolbar menu content *) - (*---------------------------------*) +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*credentialType*) +credentialType // beginDefinition; +credentialType[ service_String? systemCredentialQ ] := "SystemCredential"; +credentialType[ service_String? environmentCredentialQ ] := "Environment"; +credentialType[ service_String? savedConnectionQ ] := "ServiceConnect"; +credentialType[ service_String? serviceConnectionQ ] := "ServiceConnect"; +credentialType[ service_String ] := "None"; +credentialType // endDefinition; - Grid[ - { - {Row[{ - tr["Default Persona:"], - PopupMenu[ - Dynamic[ - currentChatSettings[ - targetObj, - "LLMEvaluator" - ], - Function[{newValue}, - CurrentValue[ - targetObj, - {TaggingRules, "ChatNotebookSettings", "LLMEvaluator"} - ] = newValue - ] - ], - defaultPersonaPopupItems - ] - }, Spacer[3]]}, - {Row[{ - tr["Default Model:"], - (* Note: Dynamic[PopupMenu[..]] so that changing the - 'show snapshot models' option updates the popup. *) - Dynamic @ PopupMenu[ - Dynamic[ - currentChatSettings[ - targetObj, - "Model" - ], - Function[{newValue}, - CurrentValue[ - targetObj, - {TaggingRules, "ChatNotebookSettings", "Model"} - ] = newValue - ] - ], - modelPopupItems, - (* This is shown if the user selects a snapshot model, - and then unchecks the 'show snapshot models' option. *) - Dynamic[ - Style[ - With[{ - modelName = currentChatSettings[targetObj, "Model"] - }, { - settings = standardizeModelData[modelName] - }, - Row[{ - getModelMenuIcon[settings, "Full"], - modelDisplayName[modelName] - }, Spacer[1]] - ], - Italic - ] - ] - ] - }, Spacer[3]]}, - {Row[{ - tr["Default Tool Call Frequency:"], - makeToolCallFrequencySlider[ targetObj ] - }, Spacer[3]]}, - {Row[{ - tr["Default Temperature:"], - makeTemperatureSlider[ - Dynamic[ - currentChatSettings[targetObj, "Temperature"], - newValue |-> ( - CurrentValue[ - targetObj, - {TaggingRules, "ChatNotebookSettings", "Temperature"} - ] = newValue; - ) - ] - ] - }, Spacer[3]]}, - - If[ TrueQ @ $useLLMServices, - Nothing, - {Row[{ - tr["Chat Completion URL:"], - makeOpenAIAPICompletionURLForm[ - Dynamic[ - currentChatSettings[targetObj, "OpenAIAPICompletionURL"], - newValue |-> ( - CurrentValue[ - targetObj, - {TaggingRules, "ChatNotebookSettings", "OpenAIAPICompletionURL"} - ] = newValue; - ) - ] - ] - }, Spacer[3]]}], - { - labeledCheckbox[ - Dynamic[ - showSnapshotModelsQ[], - newValue |-> ( - CurrentValue[$FrontEnd, { - PrivateFrontEndOptions, - "InterfaceSettings", - "Chatbook", - "ShowSnapshotModels" - }] = newValue; - - setModelPopupItems[]; - ) - ], - Row[{ - "Show temporary snapshot LLM models", - Spacer[3], - Tooltip[ - chatbookIcon["InformationTooltip", False], -"If enabled, temporary snapshot models will be included in the model selection menus. -\nSnapshot models are models that are frozen at a particular date, will not be -continuously updated, and have an expected discontinuation date." - ] - }] - ] - }, - { - makeAutomaticResultAnalysisCheckbox[targetObj] - } - }, - Alignment -> {Left, Baseline}, - Spacings -> {0, 0.7} - ] -]; +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*systemCredentialQ*) +systemCredentialQ // beginDefinition; +systemCredentialQ[ service_String ] := StringQ[ SystemCredential @ credentialKey @ service ]; +systemCredentialQ // endDefinition; -makeFrontEndAndNotebookSettingsContent // endDefinition; +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*environmentCredentialQ*) +environmentCredentialQ // beginDefinition; +environmentCredentialQ[ service_String ] := StringQ[ Environment @ credentialKey @ service ]; +environmentCredentialQ // endDefinition; (* ::**************************************************************************************************************:: *) (* ::Subsubsection::Closed:: *) -(*makeOpenAIAPICompletionURLForm*) -(* cSpell: ignore AIAPI *) -makeOpenAIAPICompletionURLForm // beginDefinition; +(*credentialKey*) +credentialKey // beginDefinition; +credentialKey[ service_String ] := ToUpperCase @ service <> "_API_KEY"; +credentialKey // endDefinition; -makeOpenAIAPICompletionURLForm[ value_ ] := Pane @ InputField[ - value, - String, - ImageSize -> { 240, Automatic }, - BaseStyle -> { FontSize -> 12 } -]; +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*savedConnectionQ*) +savedConnectionQ // beginDefinition; + +savedConnectionQ[ service_String ] := ( + Needs[ "OAuth`" -> None ]; + MatchQ[ ServiceConnections`SavedConnections @ service, { __ } ] +); + +savedConnectionQ // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*serviceConnectionQ*) +serviceConnectionQ // beginDefinition; + +serviceConnectionQ[ service_String ] := ( + Needs[ "OAuth`" -> None ]; + MatchQ[ ServiceConnections`ServiceConnections @ service, { __ } ] +); -makeOpenAIAPICompletionURLForm // endDefinition; +serviceConnectionQ // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*clearConnectionCache*) +clearConnectionCache // beginDefinition; + +clearConnectionCache[ service_String ] := + clearConnectionCache[ service, True ]; + +clearConnectionCache[ service_String, delete: True|False ] := ( + Needs[ "Wolfram`LLMFunctions`" -> None ]; + If[ delete, + Needs[ "OAuth`" -> None ]; + ServiceConnections`DeleteConnection /@ ServiceConnections`SavedConnections @ service; + ServiceConnections`DeleteConnection /@ ServiceConnections`ServiceConnections @ service; + ]; + If[ AssociationQ @ Wolfram`LLMFunctions`APIs`Common`$ConnectionCache, + KeyDropFrom[ Wolfram`LLMFunctions`APIs`Common`$ConnectionCache, service ] + ]; + InvalidateServiceCache[ ]; +); + +clearConnectionCache // endDefinition; (* ::**************************************************************************************************************:: *) (* ::Section::Closed:: *) @@ -1253,6 +1438,14 @@ $loadingPopupMenu = PopupMenu[ "x", { "x" -> ProgressIndicator[ Appearance -> "P (*$verticalSpacer*) $verticalSpacer = { Pane[ "", ImageSize -> { Automatic, 20 } ], SpanFromLeft }; +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*$trashBin*) +$trashBin := Mouseover[ + Insert[ chatbookIcon[ "ToolManagerBin", False ], GrayLevel[ 0.65 ], { 1, 1, 1 } ], + Insert[ chatbookIcon[ "ToolManagerBin", False ], Hue[ 0.59, 0.9, 0.93 ], { 1, 1, 1 } ] +]; + (* ::**************************************************************************************************************:: *) (* ::Subsection::Closed:: *) (*$resetButton*) @@ -1317,6 +1510,9 @@ resetChatPreferences[ "Tools" ] := ( resetChatPreferences[ "Services" ] := ( (* TODO: choice dialog to clear service connections *) + Needs[ "LLMServices`" -> None ]; + LLMServices`ResetServices[ ]; + InvalidateServiceCache[ ]; resetChatPreferences[ "Notebooks" ]; ); diff --git a/Source/Chatbook/Services.wl b/Source/Chatbook/Services.wl index b2dbdab2..62e29afc 100644 --- a/Source/Chatbook/Services.wl +++ b/Source/Chatbook/Services.wl @@ -5,6 +5,7 @@ BeginPackage[ "Wolfram`Chatbook`Services`" ]; (* :!CodeAnalysis::BeginBlock:: *) HoldComplete[ + `$allowConnectionDialog; `$availableServices; `$enableLLMServices; `$serviceCache; @@ -28,12 +29,13 @@ $ContextAliases[ "llm`" ] = "LLMServices`"; (* ::**************************************************************************************************************:: *) (* ::Section::Closed:: *) (*Configuration*) -$enableLLMServices = Automatic; -$modelListCache = <| |>; -$modelSortOrder = { "Snapshot", "FineTuned", "DisplayName" }; -$servicesLoaded = False; -$useLLMServices := MatchQ[ $enableLLMServices, Automatic|True ] && TrueQ @ $llmServicesAvailable; -$serviceCache = None; +$allowConnectionDialog = True; +$enableLLMServices = Automatic; +$modelListCache = <| |>; +$modelSortOrder = { "Snapshot", "FineTuned", "DisplayName" }; +$servicesLoaded = False; +$useLLMServices := MatchQ[ $enableLLMServices, Automatic|True ] && TrueQ @ $llmServicesAvailable; +$serviceCache = None; $llmServicesAvailable := $llmServicesAvailable = ( PacletInstall[ "Wolfram/LLMFunctions" ]; @@ -110,7 +112,9 @@ getServiceModelList[ service_String, info_, models0_List ] := Enclose[ Module[ { models }, models = ConfirmMatch[ preprocessModelList[ service, models0 ], { ___Association }, "Models" ]; ConfirmAssert[ AssociationQ @ $serviceCache[ service ], "ServiceCache" ]; - $serviceCache[ service, "CachedModels" ] = models + $serviceCache[ service, "CachedModels" ] = models; + updateDynamics[ "Services" ]; + models ], throwInternalFailure ]; @@ -139,14 +143,45 @@ preprocessModelList // endDefinition; (*getModelListQuietly*) getModelListQuietly // beginDefinition; +getModelListQuietly[ info_Association ] /; ! $allowConnectionDialog := + Block[ { $allowConnectionDialog = True, DialogInput = $Failed & }, + getModelListQuietly @ info + ]; + (* cSpell: ignore nprmtv, genconerr, invs, nolink *) getModelListQuietly[ info_Association ] := Quiet[ - Check[ info[ "ModelList" ], Missing[ "NotConnected" ], DialogInput::nprmtv ], + checkModelList[ info, Check[ info[ "ModelList" ], Missing[ "NotConnected" ], DialogInput::nprmtv ] ], { DialogInput::nprmtv, ServiceConnect::genconerr, ServiceConnect::invs, ServiceExecute::nolink } ]; getModelListQuietly // endDefinition; +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*checkModelList*) +checkModelList // beginDefinition; + +checkModelList[ info_, models_List ] := + models; + +checkModelList[ info_, $Canceled | $Failed | Missing[ "NotConnected" ] ] := + Missing[ "NotConnected" ]; + +checkModelList[ info_, Failure[ "ConfirmationFailed", KeyValuePattern[ "Expression" :> expr_ ] ] ] := + checkModelList[ info, expr ]; + +checkModelList[ info_, _ServiceExecute ] := ( + If[ AssociationQ @ Wolfram`LLMFunctions`APIs`Common`$ConnectionCache, + KeyDropFrom[ Wolfram`LLMFunctions`APIs`Common`$ConnectionCache, info[ "Service" ] ] + ]; + Missing[ "NotConnected" ] +); + +checkModelList[ info_, other_ ] := + Missing[ "NoModelList" ]; + +checkModelList // endDefinition; + (* ::**************************************************************************************************************:: *) (* ::Subsection::Closed:: *) (*$availableServices*) From 99f00165c23524974a65aac64fb0cd10678a7847 Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Wed, 13 Dec 2023 10:44:03 -0500 Subject: [PATCH 32/50] Bugfix: do not check API key with legacy methods when using LLMServices --- Source/Chatbook/SendChat.wl | 9 +-------- 1 file changed, 1 insertion(+), 8 deletions(-) diff --git a/Source/Chatbook/SendChat.wl b/Source/Chatbook/SendChat.wl index d61a07cf..305a0e3d 100644 --- a/Source/Chatbook/SendChat.wl +++ b/Source/Chatbook/SendChat.wl @@ -67,7 +67,7 @@ $buffer = ""; sendChat // beginDefinition; sendChat[ evalCell_, nbo_, settings0_ ] /; $useLLMServices := catchTopAs[ ChatbookAction ] @ Enclose[ - Module[ { cells0, cells, target, settings, id, key, messages, data, persona, cell, cellObject, container, task }, + Module[ { cells0, cells, target, settings, messages, data, persona, cell, cellObject, container, task }, initFETaskWidget @ nbo; @@ -92,15 +92,8 @@ sendChat[ evalCell_, nbo_, settings0_ ] /; $useLLMServices := catchTopAs[ Chatbo AppendTo[ settings, "ChatGroupSettings" -> getChatGroupSettings @ evalCell ] ]; - id = Lookup[ settings, "ID" ]; - key = toAPIKey[ Automatic, id ]; - If[ ! settings[ "IncludeHistory" ], cells = { evalCell } ]; - If[ ! StringQ @ key, throwFailure[ "NoAPIKey" ] ]; - - settings[ "OpenAIKey" ] = key; - { messages, data } = Reap[ ConfirmMatch[ constructMessages[ settings, cells ], From 5872fd31578c45fe3eccbddeef541997236d3a04 Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Thu, 14 Dec 2023 10:00:28 -0500 Subject: [PATCH 33/50] Support scopes other than `$FrontEnd` in preferences controls --- Source/Chatbook/PreferencesContent.wl | 330 +++++++++++++++++--------- 1 file changed, 218 insertions(+), 112 deletions(-) diff --git a/Source/Chatbook/PreferencesContent.wl b/Source/Chatbook/PreferencesContent.wl index eda9a962..c95aefd8 100644 --- a/Source/Chatbook/PreferencesContent.wl +++ b/Source/Chatbook/PreferencesContent.wl @@ -3,7 +3,10 @@ BeginPackage[ "Wolfram`Chatbook`PreferencesContent`" ]; HoldComplete[ + `$preferencesScope; `createPreferencesContent; + `makeModelSelector; + `makePersonaSelector; `openPreferencesPage; ]; @@ -28,6 +31,105 @@ Needs[ "Wolfram`Chatbook`UI`" ]; $preferencesPages = { "Notebooks", "Services", "Personas", "Tools" }; $$preferencesPage = Alternatives @@ $preferencesPages; +$preferencesScope := $FrontEnd; +$inFrontEndScope := MatchQ[ OwnValues @ $preferencesScope, { _ :> $FrontEnd|_FrontEndObject } ]; + +(* ::**************************************************************************************************************:: *) +(* ::Section::Closed:: *) +(*Scope Utilities*) + +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*expandScope*) +expandScope // beginDefinition; +expandScope // Attributes = { HoldFirst }; + +expandScope[ expr_ ] := ReleaseHold[ + HoldComplete @ expr /. + OwnValues @ $preferencesScope /. + HoldPattern @ $scopePlaceholder :> $preferencesScope +]; + +expandScope // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*scopeInitialization*) +scopeInitialization // beginDefinition; + +scopeInitialization[ Initialization :> init_ ] := + expandScope[ Initialization :> Block[ { $scopePlaceholder := $preferencesScope }, init ] ]; + +scopeInitialization /: RuleDelayed[ Initialization, scopeInitialization[ init_ ] ] := + scopeInitialization[ Initialization :> init ]; + +scopeInitialization // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*scopedDynamic*) +scopedDynamic // beginDefinition; +scopedDynamic // Attributes = { HoldFirst }; + +scopedDynamic[ expr_, handlers0: Except[ _Rule|_RuleDelayed ], args___ ] := + With[ { handlers = handlers0 /. (f_ &) :> (Block[ { $scopePlaceholder = $preferencesScope }, f ] &) }, + expandScope @ Dynamic[ expr, handlers, args ] + ]; + +scopedDynamic[ args___ ] := + expandScope @ Dynamic @ args; + +scopedDynamic // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*scopedTrackedDynamic*) +scopedTrackedDynamic // beginDefinition; +scopedTrackedDynamic // Attributes = { HoldFirst }; + +scopedTrackedDynamic[ expr_, args___ ] := + expandScope @ trackedDynamic[ Block[ { $scopePlaceholder = $preferencesScope }, expr ], args ]; + +scopedTrackedDynamic // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*currentTabPageDynamic*) +currentTabPageDynamic // beginDefinition; + +currentTabPageDynamic[ scope_FrontEndObject ] := Dynamic @ CurrentValue[ + $FrontEnd, + { PrivateFrontEndOptions, "DialogSettings", "Preferences", "TabSettings", "AI", "Top" }, + "Notebooks" +]; + +currentTabPageDynamic[ scope_ ] := Dynamic @ CurrentValue[ + scope, + { TaggingRules, "ChatNotebookSettings", "CurrentPreferencesTab" }, + "Notebooks" +]; + +currentTabPageDynamic // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*currentTabPage*) +currentTabPage // beginDefinition; + +currentTabPage[ scope_FrontEndObject ] := CurrentValue[ + $FrontEnd, + { PrivateFrontEndOptions, "DialogSettings", "Preferences", "TabSettings", "AI", "Top" }, + "Notebooks" +]; + +currentTabPage[ scope_ ] := CurrentValue[ + scope, + { TaggingRules, "ChatNotebookSettings", "CurrentPreferencesTab" }, + "Notebooks" +]; + +currentTabPage // endDefinition; + (* ::**************************************************************************************************************:: *) (* ::Section::Closed:: *) (*Main*) @@ -55,11 +157,7 @@ createPreferencesContent[ ] := Enclose[ { "Personas" , "Personas" -> personaSettings }, { "Tools" , "Tools" -> toolSettings } }, - Dynamic @ CurrentValue[ - $FrontEnd, - { PrivateFrontEndOptions, "DialogSettings", "Preferences", "TabSettings", "AI", "Top" }, - "Notebooks" - ], + currentTabPageDynamic @ $preferencesScope, Background -> None, FrameMargins -> { { 2, 2 }, { 2, 3 } }, ImageMargins -> { { 10, 10 }, { 2, 2 } }, @@ -99,13 +197,13 @@ createPreferencesContent // endDefinition; preferencesContent // beginDefinition; (* Content for the "Notebooks" tab: *) -preferencesContent[ "Notebooks" ] := trackedDynamic[ notebookSettingsPanel[ ], { "Models" } ]; +preferencesContent[ "Notebooks" ] := scopedTrackedDynamic[ notebookSettingsPanel[ ], { "Models" } ]; (* Content for the "Personas" tab: *) -preferencesContent[ "Personas" ] := trackedDynamic[ personaSettingsPanel[ ], { "Personas" } ]; +preferencesContent[ "Personas" ] := scopedTrackedDynamic[ personaSettingsPanel[ ], { "Personas" } ]; (* Content for the "Services" tab: *) -preferencesContent[ "Services" ] := trackedDynamic[ servicesSettingsPanel[ ], { "Models", "Services" } ]; +preferencesContent[ "Services" ] := scopedTrackedDynamic[ servicesSettingsPanel[ ], { "Models", "Services" } ]; (* Content for the "Tools" tab: *) preferencesContent[ "Tools" ] := toolSettingsPanel[ ]; @@ -127,7 +225,7 @@ notebookSettingsPanel[ ] := Pane[ { display = ProgressIndicator[ Appearance -> "Percolate" ] }, Dynamic[ display ], (* createNotebookSettingsPanel is called to initialize the content of the panel: *) - Initialization :> (display = createNotebookSettingsPanel[ ]), + Initialization :> scopeInitialization[ display = createNotebookSettingsPanel[ ] ], SynchronousInitialization -> False ], FrameMargins -> { { 8, 8 }, { 13, 13 } }, @@ -144,24 +242,21 @@ createNotebookSettingsPanel // beginDefinition; createNotebookSettingsPanel[ ] := Enclose[ Module[ { - defaultSettingsLabel, defaultSettingsContent, + defaultSettingsContent, interfaceLabel, interfaceContent, featuresLabel, featuresContent, content }, - (* Label for the default settings section using a style from SystemDialog.nb: *) - defaultSettingsLabel = Style[ "Default Settings", "subsectionText" ]; - (* Retrieve and confirm the content for default settings: *) defaultSettingsContent = ConfirmMatch[ - trackedDynamic[ makeDefaultSettingsContent[ ], "Preferences" ], + scopedTrackedDynamic[ makeDefaultSettingsContent[ ], "Preferences" ], _Dynamic, "DefaultSettings" ]; (* Label for the interface section using a style from SystemDialog.nb: *) - interfaceLabel = Style[ "Chat Notebook Interface", "subsectionText" ]; + interfaceLabel = Style[ "Chat Notebook Cells", "subsectionText" ]; (* Retrieve and confirm the content for the chat notebook interface, ensuring it is not an error from makeInterfaceContent: *) @@ -185,7 +280,6 @@ createNotebookSettingsPanel[ ] := Enclose[ (* Assemble the default settings and interface content into a grid layout: *) content = Grid[ { - { defaultSettingsLabel }, { defaultSettingsContent }, { Spacer[ 1 ] }, { Spacer[ 1 ] }, @@ -197,7 +291,7 @@ createNotebookSettingsPanel[ ] := Enclose[ { featuresContent } }, Alignment -> { Left, Baseline }, - Dividers -> { False, { 4 -> True, 8 -> True } }, + Dividers -> { False, { 3 -> True, 7 -> True } }, ItemSize -> { Fit, Automatic }, Spacings -> { 0, 0.7 } ]; @@ -220,9 +314,9 @@ makeDefaultSettingsContent[ ] := Enclose[ (* Checkbox to enable automatic assistance for normal shift-enter evaluations: *) assistanceCheckbox = ConfirmMatch[ makeAssistanceCheckbox[ ], _Style, "AssistanceCheckbox" ]; (* The personaSelector is a pop-up menu for selecting the default persona: *) - personaSelector = ConfirmMatch[ makePersonaSelector[ ], _Style, "PersonaSelector" ]; + personaSelector = ConfirmMatch[ makePersonaSelector[ ], _Dynamic, "PersonaSelector" ]; (* The modelSelector is a dynamic module containing menus to select the service and model separately: *) - modelSelector = ConfirmMatch[ makeModelSelector[ ], _DynamicModule, "ModelSelector" ]; + modelSelector = ConfirmMatch[ makeModelSelector[ ], _Dynamic, "ModelSelector" ]; (* The temperatureInput is an input field for setting the default 'temperature' for responses: *) temperatureInput = ConfirmMatch[ makeTemperatureInput[ ], _Style, "TemperatureInput" ]; @@ -247,28 +341,29 @@ makeDefaultSettingsContent // endDefinition; (* ::Subsubsection::Closed:: *) (*makePersonaSelector*) makePersonaSelector // beginDefinition; +makePersonaSelector[ ] := scopedTrackedDynamic[ makePersonaSelector0[ ], { "Personas" } ]; +makePersonaSelector // endDefinition; + +makePersonaSelector0 // beginDefinition; (* Top-level function without arguments, calls the version with personas from GetPersonasAssociation *) -makePersonaSelector[ ] := - makePersonaSelector @ GetPersonasAssociation[ ]; +makePersonaSelector0[ ] := + makePersonaSelector0 @ GetPersonasAssociation[ ]; -(* Overload of makePersonaSelector that takes an Association of personas, +(* Overload of makePersonaSelector0 that takes an Association of personas, converts it to a list of labels for PopupMenu *) -makePersonaSelector[ personas_Association? AssociationQ ] := - makePersonaSelector @ KeyValueMap[ personaPopupLabel, personas ]; +makePersonaSelector0[ personas_Association? AssociationQ ] := + makePersonaSelector0 @ KeyValueMap[ personaPopupLabel, personas ]; -(* Overload of makePersonaSelector that takes a list of rules where each rule is a string to an association, +(* Overload of makePersonaSelector0 that takes a list of rules where each rule is a string to an association, creates a PopupMenu with this list *) -makePersonaSelector[ personas: { (_String -> _).. } ] := +makePersonaSelector0[ personas: { (_String -> _).. } ] := highlightControl[ Row @ { - "Default Persona:", + "Persona:", Spacer[ 3 ], PopupMenu[ - Dynamic[ - currentChatSettings[ $FrontEnd, "LLMEvaluator" ], - (CurrentValue[ $FrontEnd, { TaggingRules, "ChatNotebookSettings", "LLMEvaluator" } ] = #1) & - ], + scopedDynamic @ CurrentChatSettings[ $preferencesScope, "LLMEvaluator" ], personas ] }, @@ -276,7 +371,7 @@ makePersonaSelector[ personas: { (_String -> _).. } ] := "LLMEvaluator" ]; -makePersonaSelector // endDefinition; +makePersonaSelector0 // endDefinition; (* ::**************************************************************************************************************:: *) (* ::Subsubsubsection::Closed:: *) @@ -295,14 +390,19 @@ personaPopupLabel // endDefinition; (* ::Subsubsection::Closed:: *) (*makeModelSelector*) makeModelSelector // beginDefinition; +makeModelSelector[ ] := scopedTrackedDynamic[ makeModelSelector0[ ], { "Models", "Services" } ]; +makeModelSelector // endDefinition; -makeModelSelector[ ] := - makeModelSelector @ $availableServices; -makeModelSelector[ services_Association? AssociationQ ] := Enclose[ +makeModelSelector0 // beginDefinition; + +makeModelSelector0[ ] := + makeModelSelector0 @ $availableServices; + +makeModelSelector0[ services_Association? AssociationQ ] := Enclose[ DynamicModule[ { default, service, model, state, serviceSelector, modelSelector, highlight }, - default = currentChatSettings[ $FrontEnd, "Model" ]; + default = currentChatSettings[ $preferencesScope, "Model" ]; service = ConfirmBy[ extractServiceName @ default, StringQ, "ServiceName" ]; model = ConfirmBy[ extractModelName @ default , StringQ, "ModelName" ]; state = If[ modelListCachedQ @ service, "Loaded", "Loading" ]; @@ -329,11 +429,11 @@ makeModelSelector[ services_Association? AssociationQ ] := Enclose[ highlightControl[ Row @ { - highlight[ "Default LLM Service:", serviceSelector, "ModelService" ], + highlight[ "LLM Service:", serviceSelector, "ModelService" ], Spacer[ 5 ], highlight[ - "Default Model:", - Dynamic[ + "Model:", + Dynamic[ If[ state === "Loading", $loadingPopupMenu, modelSelector ], TrackedSymbols :> { state, modelSelector } ], @@ -344,7 +444,7 @@ makeModelSelector[ services_Association? AssociationQ ] := Enclose[ "Model" ], - Initialization :> ( + Initialization :> scopeInitialization[ modelSelector = catchAlways @ makeModelNameSelector[ Dynamic @ service, Dynamic @ model, @@ -352,7 +452,7 @@ makeModelSelector[ services_Association? AssociationQ ] := Enclose[ Dynamic @ state ]; state = "Loaded"; - ), + ], SynchronousInitialization -> False, SynchronousUpdating -> False, UnsavedVariables :> { state } @@ -360,7 +460,7 @@ makeModelSelector[ services_Association? AssociationQ ] := Enclose[ throwInternalFailure ]; -makeModelSelector // endDefinition; +makeModelSelector0 // endDefinition; (* ::**************************************************************************************************************:: *) (* ::Subsubsubsection::Closed:: *) @@ -375,8 +475,8 @@ makeServiceSelector[ services_ ] := PopupMenu[ - Dynamic[ - extractServiceName @ CurrentChatSettings[ $FrontEnd, "Model" ], + scopedDynamic[ + extractServiceName @ CurrentChatSettings[ $preferencesScope, "Model" ], serviceSelectCallback[ Dynamic @ service, Dynamic @ model, Dynamic @ modelSelector, Dynamic @ state ] ], KeyValueMap[ popupValue[ #1, #2[ "Service" ], #2[ "Icon" ] ] &, services ] @@ -409,16 +509,18 @@ serviceSelectCallback[ model = getServiceDefaultModel @ selected; (* Store the service/model in FE settings: *) - CurrentChatSettings[ $FrontEnd, "Model" ] = <| "Service" -> service, "Name" -> model |>; + CurrentChatSettings[ $preferencesScope, "Model" ] = <| "Service" -> service, "Name" -> model |>; (* Finish loading the model name selector: *) If[ state === "Loading", - SessionSubmit[ - modelSelector = makeModelNameSelector[ - Dynamic @ service, - Dynamic @ model, - Dynamic @ modelSelector, - Dynamic @ state + expandScope @ SessionSubmit[ + Block[ { $scopePlaceholder := $preferencesScope }, + modelSelector = makeModelNameSelector[ + Dynamic @ service, + Dynamic @ model, + Dynamic @ modelSelector, + Dynamic @ state + ] ]; state = "Loaded" ], @@ -473,22 +575,22 @@ makeModelNameSelector[ ] ]; - current = extractModelName @ CurrentChatSettings[ $FrontEnd, "Model" ]; + current = extractModelName @ CurrentChatSettings[ $preferencesScope, "Model" ]; default = ConfirmBy[ getServiceDefaultModel @ service, StringQ, "DefaultName" ]; fallback = <| "Service" -> service, "Name" -> default |>; If[ ! MemberQ[ models, KeyValuePattern[ "Name" -> current ] ], - CurrentValue[ $FrontEnd, { TaggingRules, "ChatNotebookSettings", "Model" } ] = fallback + CurrentValue[ $preferencesScope, { TaggingRules, "ChatNotebookSettings", "Model" } ] = fallback ]; With[ { m = fallback }, PopupMenu[ - Dynamic[ + scopedDynamic[ Replace[ - extractModelName @ CurrentChatSettings[ $FrontEnd, "Model" ], + extractModelName @ CurrentChatSettings[ $preferencesScope, "Model" ], { Except[ _String ] :> ( - CurrentValue[ $FrontEnd, { TaggingRules, "ChatNotebookSettings", "Model" } ] = m + CurrentValue[ $preferencesScope, { TaggingRules, "ChatNotebookSettings", "Model" } ] = m ) } ], @@ -512,9 +614,9 @@ modelNameInputField // beginDefinition; modelNameInputField[ Dynamic[ service_ ], Dynamic[ model_ ], Dynamic[ modelSelector_ ], Dynamic[ state_ ] ] := prefsInputField[ "Model:", - Dynamic[ + scopedDynamic[ Replace[ - extractModelName @ CurrentChatSettings[ $FrontEnd, "Model" ], + extractModelName @ CurrentChatSettings[ $preferencesScope, "Model" ], Except[ _String ] :> "" ], { None, modelSelectCallback[ Dynamic @ service, Dynamic @ model ] } @@ -578,10 +680,10 @@ modelSelectCallback[ (* Remember the selected model for the given service, so it will be automatically chosen when choosing this service again: *) - CurrentValue[ $FrontEnd, { TaggingRules, "ChatNotebookSettings", "ServiceDefaultModel", service } ] = model; + CurrentValue[ $preferencesScope, { TaggingRules, "ChatNotebookSettings", "ServiceDefaultModel", service } ] = model; (* Store the service/model in FE settings: *) - CurrentValue[ $FrontEnd, { TaggingRules, "ChatNotebookSettings", "Model" } ] = <| + CurrentValue[ $preferencesScope, { TaggingRules, "ChatNotebookSettings", "Model" } ] = <| "Service" -> service, "Name" -> model |> @@ -598,9 +700,9 @@ makeAssistanceCheckbox // beginDefinition; makeAssistanceCheckbox[ ] := highlightControl[ prefsCheckbox[ - Dynamic[ - TrueQ @ CurrentChatSettings[ $FrontEnd, "Assistance" ], - (CurrentChatSettings[ $FrontEnd, "Assistance" ] = #1) & + scopedDynamic[ + TrueQ @ CurrentChatSettings[ $preferencesScope, "Assistance" ], + (CurrentChatSettings[ $preferencesScope, "Assistance" ] = #1) & ], infoTooltip[ "Enable automatic assistance", @@ -621,11 +723,11 @@ makeTemperatureInput // beginDefinition; makeTemperatureInput[ ] := highlightControl[ prefsInputField[ "Temperature:", - Dynamic[ - CurrentChatSettings[ $FrontEnd, "Temperature" ], + scopedDynamic[ + CurrentChatSettings[ $preferencesScope, "Temperature" ], { None, - If[ NumberQ @ #, CurrentChatSettings[ $FrontEnd, "Temperature" ] = # ] & + If[ NumberQ @ #, CurrentChatSettings[ $preferencesScope, "Temperature" ] = # ] & } ], Number, @@ -673,9 +775,9 @@ makeFormatCheckbox // beginDefinition; makeFormatCheckbox[ ] := highlightControl[ prefsCheckbox[ - Dynamic[ - TrueQ @ CurrentChatSettings[ $FrontEnd, "AutoFormat" ], - (CurrentChatSettings[ $FrontEnd, "AutoFormat" ] = #1) & + scopedDynamic[ + TrueQ @ CurrentChatSettings[ $preferencesScope, "AutoFormat" ], + (CurrentChatSettings[ $preferencesScope, "AutoFormat" ] = #1) & ], "Format chat output" ], @@ -692,9 +794,9 @@ makeIncludeHistoryCheckbox // beginDefinition; makeIncludeHistoryCheckbox[ ] := highlightControl[ prefsCheckbox[ - Dynamic[ - MatchQ[ CurrentChatSettings[ $FrontEnd, "IncludeHistory" ], True|Automatic ], - (CurrentChatSettings[ $FrontEnd, "IncludeHistory" ] = #1) & + scopedDynamic[ + MatchQ[ CurrentChatSettings[ $preferencesScope, "IncludeHistory" ], True|Automatic ], + (CurrentChatSettings[ $preferencesScope, "IncludeHistory" ] = #1) & ], infoTooltip[ "Include chat history", @@ -716,12 +818,12 @@ makeChatHistoryLengthInput[ ] := highlightControl[ infoTooltip[ prefsInputField[ "Chat history length:", - Dynamic[ - CurrentChatSettings[ $FrontEnd, "ChatHistoryLength" ], + scopedDynamic[ + CurrentChatSettings[ $preferencesScope, "ChatHistoryLength" ], { None, If[ NumberQ @ # && NonNegative @ #, - CurrentChatSettings[ $FrontEnd, "ChatHistoryLength" ] = Floor[ # ] + CurrentChatSettings[ $preferencesScope, "ChatHistoryLength" ] = Floor[ # ] ] & } ], @@ -743,9 +845,9 @@ makeMergeMessagesCheckbox // beginDefinition; makeMergeMessagesCheckbox[ ] := highlightControl[ prefsCheckbox[ - Dynamic[ - MatchQ[ CurrentChatSettings[ $FrontEnd, "MergeMessages" ], True|Automatic ], - (CurrentChatSettings[ $FrontEnd, "MergeMessages" ] = #1) & + scopedDynamic[ + MatchQ[ CurrentChatSettings[ $preferencesScope, "MergeMessages" ], True|Automatic ], + (CurrentChatSettings[ $preferencesScope, "MergeMessages" ] = #1) & ], infoTooltip[ "Merge chat messages", @@ -796,7 +898,7 @@ makeMultimodalMenu[ ] := highlightControl[ { Style[ "Enable multimodal content: ", "leadinText" ], PopupMenu[ - Dynamic @ CurrentChatSettings[ $FrontEnd, "Multimodal" ], + scopedDynamic @ CurrentChatSettings[ $preferencesScope, "Multimodal" ], { Automatic -> "Automatic by model", True -> "Always enabled", @@ -826,7 +928,7 @@ makeToolsEnabledMenu[ ] := highlightControl[ { Style[ "Enable tools: ", "leadinText" ], PopupMenu[ - Dynamic @ CurrentChatSettings[ $FrontEnd, "ToolsEnabled" ], + scopedDynamic @ CurrentChatSettings[ $preferencesScope, "ToolsEnabled" ], { Automatic -> "Automatic by model", True -> "Always enabled", @@ -858,16 +960,16 @@ makeToolCallFrequencySelector[ ] := highlightControl[ { Style[ "Tool call frequency:", "leadinText" ], PopupMenu[ - Dynamic[ + scopedDynamic[ type, Function[ If[ # === Automatic , type = Automatic; - CurrentChatSettings[ $FrontEnd, "ToolCallFrequency" ] = Automatic + CurrentChatSettings[ $preferencesScope, "ToolCallFrequency" ] = Automatic , type = "Custom"; - CurrentChatSettings[ $FrontEnd, "ToolCallFrequency" ] = 0.5 + CurrentChatSettings[ $preferencesScope, "ToolCallFrequency" ] = 0.5 ] ] ], @@ -886,12 +988,12 @@ makeToolCallFrequencySelector[ ] := highlightControl[ Spacer[ 5 ], Style[ "Rare", "defaultSubtext" ], Slider[ - Dynamic[ + scopedDynamic[ frequency, { Function[ frequency = # ], Function[ - CurrentChatSettings[ $FrontEnd, "ToolCallFrequency" ] = #; + CurrentChatSettings[ $preferencesScope, "ToolCallFrequency" ] = #; frequency = # ] } @@ -913,10 +1015,11 @@ makeToolCallFrequencySelector[ ] := highlightControl[ BaselinePosition -> 1, Spacings -> 0.5 ], - Initialization :> With[ { val = CurrentChatSettings[ $FrontEnd, "ToolCallFrequency" ] }, - type = If[ NumberQ @ val, "Custom", Automatic ]; - frequency = If[ NumberQ @ val, val, 0.5 ]; - ] + Initialization :> scopeInitialization @ + With[ { val = CurrentChatSettings[ $preferencesScope, "ToolCallFrequency" ] }, + type = If[ NumberQ @ val, "Custom", Automatic ]; + frequency = If[ NumberQ @ val, val, 0.5 ]; + ] ], "Notebooks", "ToolCallFrequency" @@ -937,7 +1040,7 @@ servicesSettingsPanel[ ] := Enclose[ Module[ { settingsLabel, settings, serviceGrid }, settingsLabel = Style[ "Registered Services", "subsectionText" ]; - settings = ConfirmMatch[ makeModelSelector[ ], _DynamicModule, "ServicesSettings" ]; + settings = ConfirmMatch[ makeModelSelector[ ], _Dynamic, "ServicesSettings" ]; serviceGrid = ConfirmMatch[ makeServiceGrid[ ], _Grid, "ServiceGrid" ]; Pane[ @@ -1053,7 +1156,7 @@ makeServiceAuthenticationDisplay[ service_String ] := DynamicModule[ { display }, display = ProgressIndicator[ Appearance -> "Percolate" ]; Dynamic[ display, TrackedSymbols :> { display } ], - Initialization :> createServiceAuthenticationDisplay[ service, Dynamic[ display ] ], + Initialization :> scopeInitialization @ createServiceAuthenticationDisplay[ service, Dynamic[ display ] ], SynchronousInitialization -> False ]; @@ -1069,7 +1172,11 @@ createServiceAuthenticationDisplay[ service_, Dynamic[ display_ ] ] := Enclose[ type = ConfirmBy[ credentialType @ service, StringQ, "CredentialType" ]; display = Row[ { - Pane[ type, ImageSize -> { 120, Automatic } ], + If[ type === "None", + Style[ "\[Checkmark]", ShowContents -> False ], + Style[ "\[Checkmark]", FontColor -> Gray ] + ], + Spacer[ 20 ], connectOrDisconnectButton[ service, type, Dynamic @ display ] }, Alignment -> { Left, Baseline } @@ -1119,7 +1226,7 @@ personaSettingsPanel[ ] := DynamicModule[ { display = ProgressIndicator[ Appearance -> "Percolate" ] }, Dynamic[ display ], - Initialization :> (display = CreatePersonaManagerPanel[ ]), + Initialization :> scopeInitialization[ display = CreatePersonaManagerPanel[ ] ], SynchronousInitialization -> False, UnsavedVariables :> { display } ]; @@ -1139,7 +1246,7 @@ toolSettingsPanel[ ] := DynamicModule[ { display = ProgressIndicator[ Appearance -> "Percolate" ] }, Dynamic[ display ], - Initialization :> (display = CreateLLMToolManagerPanel[ ]), + Initialization :> scopeInitialization[ display = CreateLLMToolManagerPanel[ ] ], SynchronousInitialization -> False, UnsavedVariables :> { display } ]; @@ -1257,7 +1364,7 @@ ensureServiceName[ symbol_Symbol ] := ]; ensureServiceName[ symbol_Symbol ] := - With[ { service = extractServiceName @ CurrentChatSettings[ $FrontEnd, "Model" ] }, + With[ { service = extractServiceName @ CurrentChatSettings[ $preferencesScope, "Model" ] }, (symbol = service) /; StringQ @ service ]; @@ -1289,14 +1396,14 @@ getServiceDefaultModel // beginDefinition; getServiceDefaultModel[ selected_String ] := Replace[ (* Use the last model name that was selected for this service if it exists: *) CurrentValue[ - $FrontEnd, + $preferencesScope, { TaggingRules, "ChatNotebookSettings", "ServiceDefaultModel", selected } ], (* Otherwise determine a starting model from the registered service: *) $$unspecified :> ( CurrentValue[ - $FrontEnd, + $preferencesScope, { TaggingRules, "ChatNotebookSettings", "ServiceDefaultModel", selected } ] = chooseDefaultModelName @ selected ) @@ -1337,8 +1444,8 @@ disconnectService[ service_String ] := Unset @ SystemCredential @ key; SetEnvironment[ key -> None ]; clearConnectionCache @ service; - If[ extractServiceName @ CurrentChatSettings[ $FrontEnd, "Model" ] === service, - CurrentChatSettings[ $FrontEnd, "Model" ] = $DefaultModel + If[ extractServiceName @ CurrentChatSettings[ $preferencesScope, "Model" ] === service, + CurrentChatSettings[ $preferencesScope, "Model" ] = $DefaultModel ]; updateDynamics[ "Services" ] ]; @@ -1449,7 +1556,7 @@ $trashBin := Mouseover[ (* ::**************************************************************************************************************:: *) (* ::Subsection::Closed:: *) (*$resetButton*) -$resetButton = +$resetButton := Module[ { icon, label }, icon = Style[ Dynamic @ RawBoxes @ FEPrivate`FrontEndResource[ "FEBitmaps", "SyntaxColorResetIcon" ][ @@ -1463,14 +1570,11 @@ $resetButton = Alignment -> { Automatic, Baseline } ]; - Button[ + expandScope @ Button[ label, Needs[ "Wolfram`Chatbook`" -> None ]; - resetChatPreferences @ CurrentValue[ - $FrontEnd, - { PrivateFrontEndOptions, "DialogSettings", "Preferences", "TabSettings", "AI", "Top" } - ] + resetChatPreferences @ currentTabPage @ $preferencesScope , BaseStyle -> { FontFamily -> Dynamic @ FrontEnd`CurrentValue[ "ControlsFontFamily" ], @@ -1487,19 +1591,20 @@ $resetButton = (*resetChatPreferences*) resetChatPreferences // beginDefinition; -resetChatPreferences[ "Notebooks" ] := ( +resetChatPreferences[ "Notebooks" ] := expandScope[ FrontEndExecute @ FrontEnd`RemoveOptions[ - $FrontEnd, - { System`LLMEvaluator, { TaggingRules, "ChatNotebookSettings" } } + $preferencesScope, + { LLMEvaluator, { TaggingRules, "ChatNotebookSettings" } } ]; updateDynamics[ "Preferences" ]; -); +]; resetChatPreferences[ "Personas" ] := + (* TODO: this won't work when $preferencesScope is something other than $FrontEnd *) With[ { path = Sequence[ PrivateFrontEndOptions, "InterfaceSettings", "Chatbook" ] }, (* TODO: choice dialog to uninstall personas *) - CurrentValue[ $FrontEnd, { path, "VisiblePersonas" } ] = $corePersonaNames; - CurrentValue[ $FrontEnd, { path, "PersonaFavorites" } ] = $corePersonaNames; + CurrentValue[ $preferencesScope, { path, "VisiblePersonas" } ] = $corePersonaNames; + CurrentValue[ $preferencesScope, { path, "PersonaFavorites" } ] = $corePersonaNames; resetChatPreferences[ "Notebooks" ]; ]; @@ -1542,7 +1647,8 @@ openPreferencesPage // endDefinition; (* ::Subsection::Closed:: *) (*highlightControl*) highlightControl // beginDefinition; -highlightControl[ expr_, tab_, id_ ] := Style[ expr, Background -> highlightColor[ tab, id ] ]; +highlightControl[ expr_, tab_, id_ ] /; $inFrontEndScope := Style[ expr, Background -> highlightColor[ tab, id ] ]; +highlightControl[ expr_, tab_, id_ ] := Style @ expr; highlightControl // endDefinition; (* ::**************************************************************************************************************:: *) From d14ceecd20e7cc356d240e62b44833955857244b Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Thu, 14 Dec 2023 10:01:15 -0500 Subject: [PATCH 34/50] Move cloud toolbar content to separate file and use new preferences controls --- Source/Chatbook/CloudToolbar.wl | 107 +++++++++++++++++++++++ Source/Chatbook/Dialogs.wl | 1 + Source/Chatbook/Main.wl | 1 + Source/Chatbook/UI.wl | 145 +------------------------------- 4 files changed, 111 insertions(+), 143 deletions(-) create mode 100644 Source/Chatbook/CloudToolbar.wl diff --git a/Source/Chatbook/CloudToolbar.wl b/Source/Chatbook/CloudToolbar.wl new file mode 100644 index 00000000..13c71667 --- /dev/null +++ b/Source/Chatbook/CloudToolbar.wl @@ -0,0 +1,107 @@ +(* ::Section::Closed:: *) +(*Package Header*) +BeginPackage[ "Wolfram`Chatbook`CloudToolbar`" ]; + +HoldComplete[ + `makeChatCloudDockedCellContents; +]; + +Begin[ "`Private`" ]; + +Needs[ "Wolfram`Chatbook`" ]; +Needs[ "Wolfram`Chatbook`Common`" ]; +Needs[ "Wolfram`Chatbook`Dialogs`" ]; +Needs[ "Wolfram`Chatbook`Dynamics`" ]; +Needs[ "Wolfram`Chatbook`PreferencesContent`" ]; + +(* ::**************************************************************************************************************:: *) +(* ::Section::Closed:: *) +(*Configuration*) +$notebookTypeLabelOptions = Sequence[ + FontColor -> RGBColor[ "#333333" ], + FontFamily -> "Source Sans Pro", + FontSize -> 16, + FontWeight -> "DemiBold" +]; + +(* ::**************************************************************************************************************:: *) +(* ::Section::Closed:: *) +(*Docked Cell Contents*) + +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*makeChatCloudDockedCellContents*) +makeChatCloudDockedCellContents // beginDefinition; + +makeChatCloudDockedCellContents[ ] := + Block[ { $preferencesScope := EvaluationNotebook[ ] }, + Grid[ + { + { + Item[ $cloudChatBanner, Alignment -> Left ], + Item[ "", ItemSize -> Fit ], + makePersonaSelector[ ], + makeModelSelector[ ] + } + }, + Dividers -> { { False, False, False, True }, False }, + Spacings -> { 2, 0 }, + BaseStyle -> { "Text", FontSize -> 14, FontColor -> GrayLevel[ 0.4 ] }, + FrameStyle -> Directive[ Thickness[ 2 ], GrayLevel[ 0.9 ] ] + ] + ]; + +makeChatCloudDockedCellContents // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Section::Closed:: *) +(*Notebook Type Label*) + +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*$cloudChatBanner*) +$cloudChatBanner := $cloudChatBanner = cvExpand @ PaneSelector[ + { True -> $chatDrivenNotebookLabel, False -> $chatEnabledNotebookLabel }, + Dynamic @ TrueQ @ cv[ EvaluationNotebook[ ], "ChatDrivenNotebook" ], + ImageSize -> Automatic +]; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*$chatDrivenNotebookLabel*) +$chatDrivenNotebookLabel := Grid[ + { + { + "", + chatbookIcon[ "ChatDrivenNotebookIcon", False ], + Style[ "Chat-Driven Notebook", $notebookTypeLabelOptions ] + } + }, + Alignment -> { Automatic, Center }, + Spacings -> 0.5 +]; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*$chatEnabledNotebookLabel*) +$chatEnabledNotebookLabel := Grid[ + { + { + "", + chatbookIcon[ "ChatEnabledNotebookIcon", False ], + Style[ "Chat-Enabled Notebook", $notebookTypeLabelOptions ] + } + }, + Alignment -> { Automatic, Center }, + Spacings -> 0.5 +]; + +(* ::**************************************************************************************************************:: *) +(* ::Section::Closed:: *) +(*Package Footer*) +If[ Wolfram`ChatbookInternal`$BuildingMX, + $cloudChatBanner; +]; + +End[ ]; +EndPackage[ ]; diff --git a/Source/Chatbook/Dialogs.wl b/Source/Chatbook/Dialogs.wl index 724f7aef..3e8048e4 100644 --- a/Source/Chatbook/Dialogs.wl +++ b/Source/Chatbook/Dialogs.wl @@ -256,6 +256,7 @@ redDialogButtonLabel // endDefinition; cvExpand // beginDefinition; cvExpand // Attributes = { HoldFirst }; cvExpand[ expr_ ] := expr /. $cvRules; +cvExpand /: SetDelayed[ lhs_, cvExpand[ rhs_ ] ] := Unevaluated @ SetDelayed[ lhs, rhs ] /. $cvRules; cvExpand // endDefinition; (* ::**************************************************************************************************************:: *) diff --git a/Source/Chatbook/Main.wl b/Source/Chatbook/Main.wl index 12d526b3..5f1baeca 100644 --- a/Source/Chatbook/Main.wl +++ b/Source/Chatbook/Main.wl @@ -98,6 +98,7 @@ Block[ { $ContextPath }, Get[ "Wolfram`Chatbook`ToolManager`" ]; Get[ "Wolfram`Chatbook`PersonaManager`" ]; Get[ "Wolfram`Chatbook`ChatHistory`" ]; + Get[ "Wolfram`Chatbook`CloudToolbar`" ]; ]; (* ::**************************************************************************************************************:: *) diff --git a/Source/Chatbook/UI.wl b/Source/Chatbook/UI.wl index bc6a4eb1..b6a94692 100644 --- a/Source/Chatbook/UI.wl +++ b/Source/Chatbook/UI.wl @@ -42,6 +42,7 @@ Begin["`Private`"] Needs[ "Wolfram`Chatbook`" ]; Needs[ "Wolfram`Chatbook`Actions`" ]; +Needs[ "Wolfram`Chatbook`CloudToolbar`" ]; Needs[ "Wolfram`Chatbook`Common`" ]; Needs[ "Wolfram`Chatbook`Dynamics`" ]; Needs[ "Wolfram`Chatbook`Errors`" ]; @@ -69,108 +70,7 @@ $chatMenuWidth = 220; (* ::**************************************************************************************************************:: *) (* ::Subsection::Closed:: *) (*MakeChatCloudDockedCellContents*) -MakeChatCloudDockedCellContents[] := Grid[ - {{ - Item[$cloudChatBanner, Alignment -> Left], - Item["", ItemSize -> Fit], - Row[{"Persona", Spacer[5], trackedDynamic[$cloudPersonaChooser, "Personas"]}], - Row[{"Model", Spacer[5], trackedDynamic[$cloudModelChooser, "Models"]}] - }}, - Dividers -> {{False, False, False, True}, False}, - Spacings -> {2, 0}, - BaseStyle -> {"Text", FontSize -> 14, FontColor -> GrayLevel[0.4]}, - FrameStyle -> Directive[Thickness[2], GrayLevel[0.9]] -] - -(* ::**************************************************************************************************************:: *) -(* ::Subsubsection::Closed:: *) -(*$cloudPersonaChooser*) -$cloudPersonaChooser := PopupMenu[ - Dynamic[ - Replace[ - CurrentValue[EvaluationNotebook[], {TaggingRules, "ChatNotebookSettings", "LLMEvaluator"}], - Inherited :> Lookup[$defaultChatSettings, "LLMEvaluator", "CodeAssistant"] - ], - Function[CurrentValue[EvaluationNotebook[], {TaggingRules, "ChatNotebookSettings", "LLMEvaluator"}] = #] - ], - KeyValueMap[ - Function[{key, as}, key -> Grid[{{resizeMenuIcon[getPersonaMenuIcon[as]], personaDisplayName[key, as]}}]], - GetCachedPersonaData[] - ], - ImageSize -> {Automatic, 30}, - Alignment -> {Left, Baseline}, - BaseStyle -> {FontSize -> 12} -] - -(* ::**************************************************************************************************************:: *) -(* ::Subsubsection::Closed:: *) -(*$cloudModelChooser*) -$cloudModelChooser := PopupMenu[ - Dynamic[ - Replace[ - CurrentValue[EvaluationNotebook[], {TaggingRules, "ChatNotebookSettings", "Model"}], - Inherited :> Lookup[$defaultChatSettings, "Model", "gpt-3.5-turbo"] - ], - Function[CurrentValue[EvaluationNotebook[], {TaggingRules, "ChatNotebookSettings", "Model"}] = #] - ], - KeyValueMap[ - {modelName, settings} |-> ( - modelName -> Grid[{{getModelMenuIcon[settings], modelDisplayName[modelName]}}] - ), - (* FIXME: use the new system *) - getModelsMenuItems[] - ], - ImageSize -> {Automatic, 30}, - Alignment -> {Left, Baseline}, - BaseStyle -> {FontSize -> 12} -] - -(* ::**************************************************************************************************************:: *) -(* ::Subsubsection::Closed:: *) -(*$cloudChatBanner*) -$cloudChatBanner := PaneSelector[ - { - True -> Grid[ - { - { - "", - chatbookIcon[ "ChatDrivenNotebookIcon", False ], - Style[ - "Chat-Driven Notebook", - FontColor -> RGBColor[ "#333333" ], - FontFamily -> "Source Sans Pro", - FontSize -> 16, - FontWeight -> "DemiBold" - ] - } - }, - Alignment -> { Automatic, Center }, - Spacings -> 0.5 - ], - False -> Grid[ - { - { - "", - chatbookIcon[ "ChatEnabledNotebookIcon", False ], - Style[ - "Chat-Enabled Notebook", - FontColor -> RGBColor[ "#333333" ], - FontFamily -> "Source Sans Pro", - FontSize -> 16, - FontWeight -> "DemiBold" - ] - } - }, - Alignment -> { Automatic, Center }, - Spacings -> 0.5 - ] - }, - Dynamic @ TrueQ @ CurrentValue[ - EvaluationNotebook[ ], - { TaggingRules, "ChatNotebookSettings", "ChatDrivenNotebook" } - ], - ImageSize -> Automatic -] +MakeChatCloudDockedCellContents[] := makeChatCloudDockedCellContents[ ]; (* ::**************************************************************************************************************:: *) (* ::Section::Closed:: *) @@ -399,47 +299,6 @@ labeledCheckbox[value_, label_, enabled_ : Automatic] := (*====================================*) -makeToolCallFrequencySlider[ obj_ ] := Pane[ - Grid[ - { - { - labeledCheckbox[ - Dynamic[ - currentChatSettings[ obj, "ToolCallFrequency" ] === Automatic, - Function[ - If[ TrueQ[ # ], - CurrentValue[ obj, { TaggingRules, "ChatNotebookSettings", "ToolCallFrequency" } ] = Inherited, - CurrentValue[ obj, { TaggingRules, "ChatNotebookSettings", "ToolCallFrequency" } ] = 0.5 - ] - ] - ], - Style[ "Choose automatically", "ChatMenuLabel" ] - ] - }, - { - Pane[ - Slider[ - Dynamic[ - Replace[ currentChatSettings[ obj, "ToolCallFrequency" ], Automatic -> 0.5 ], - (CurrentValue[ obj, { TaggingRules, "ChatNotebookSettings", "ToolCallFrequency" } ] = #) & - ], - { 0, 1, 0.01 }, - (* Enabled -> Dynamic[ currentChatSettings[ obj, "ToolCallFrequency" ] =!= Automatic ], *) - ImageSize -> { 150, Automatic }, - ImageMargins -> { { 5, 0 }, { 5, 5 } } - ], - ImageSize -> { 180, Automatic }, - BaseStyle -> { FontSize -> 12 } - ], - SpanFromLeft - } - }, - Alignment -> Left, - Spacings -> { Automatic, 0 } - ], - ImageMargins -> { { 5, 0 }, { 5, 5 } } -]; - makeToolCallFrequencySlider[ obj_ ] := Module[ { checkbox, slider }, checkbox = labeledCheckbox[ From 60c26efb36e28c5fbcf5c43b0640a9278d4cabb2 Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Thu, 14 Dec 2023 10:22:23 -0500 Subject: [PATCH 35/50] Update tests for `CurrentChatSettings` --- Tests/CurrentChatSettings.wlt | 18 +++++++++++------- 1 file changed, 11 insertions(+), 7 deletions(-) diff --git a/Tests/CurrentChatSettings.wlt b/Tests/CurrentChatSettings.wlt index 82ebc151..1b2b0b2e 100644 --- a/Tests/CurrentChatSettings.wlt +++ b/Tests/CurrentChatSettings.wlt @@ -34,7 +34,7 @@ VerificationTest[ VerificationTest[ CurrentChatSettings[ "Model" ], - _String | Automatic, + KeyValuePattern @ { "Service" -> _String, "Name" -> _String } | _String | Automatic, SameTest -> MatchQ, TestID -> "CurrentChatSettings@@Tests/CurrentChatSettings.wlt:35,1-40,2" ] @@ -44,14 +44,14 @@ VerificationTest[ (*Scoped*) VerificationTest[ UsingFrontEnd @ CurrentChatSettings[ $FrontEnd, "Model" ], - _String | Automatic, + KeyValuePattern @ { "Service" -> _String, "Name" -> _String } | _String | Automatic, SameTest -> MatchQ, TestID -> "CurrentChatSettings@@Tests/CurrentChatSettings.wlt:45,1-50,2" ] VerificationTest[ UsingFrontEnd @ CurrentChatSettings[ $FrontEndSession, "Model" ], - _String | Automatic, + KeyValuePattern @ { "Service" -> _String, "Name" -> _String } | _String | Automatic, SameTest -> MatchQ, TestID -> "CurrentChatSettings@@Tests/CurrentChatSettings.wlt:52,1-57,2" ] @@ -83,9 +83,13 @@ VerificationTest[ } } ], - { Except[ "BlockModel", _String ], "BlockModel", "BlockModel" }, + { + Except[ "BlockModel", KeyValuePattern @ { "Service" -> _String, "Name" -> _String } ], + "BlockModel", + "BlockModel" + }, SameTest -> MatchQ, - TestID -> "CurrentChatSettings-ChatBlocks@@Tests/CurrentChatSettings.wlt:75,1-89,2" + TestID -> "CurrentChatSettings-ChatBlocks@@Tests/CurrentChatSettings.wlt:75,1-93,2" ] VerificationTest[ @@ -102,7 +106,7 @@ VerificationTest[ ], { "NotebookModel", "BlockModel", "BlockModel" }, SameTest -> MatchQ, - TestID -> "CurrentChatSettings-ChatBlocks@@Tests/CurrentChatSettings.wlt:91,1-106,2" + TestID -> "CurrentChatSettings-ChatBlocks@@Tests/CurrentChatSettings.wlt:95,1-110,2" ] (* ::**************************************************************************************************************:: *) @@ -125,5 +129,5 @@ VerificationTest[ ], Except[ _? FailureQ ], SameTest -> MatchQ, - TestID -> "CurrentChatSettings-Regression@@Tests/CurrentChatSettings.wlt:115,1-129,2" + TestID -> "CurrentChatSettings-Regression@@Tests/CurrentChatSettings.wlt:119,1-133,2" ] From 781db5be4ae48ae2aaf7b0c7ceac12e04458ba3f Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Thu, 14 Dec 2023 10:49:41 -0500 Subject: [PATCH 36/50] Autofix tagging rules in cloud notebooks --- Source/Chatbook/CloudToolbar.wl | 33 +++++++++++++++++++++------------ 1 file changed, 21 insertions(+), 12 deletions(-) diff --git a/Source/Chatbook/CloudToolbar.wl b/Source/Chatbook/CloudToolbar.wl index 13c71667..d6705bce 100644 --- a/Source/Chatbook/CloudToolbar.wl +++ b/Source/Chatbook/CloudToolbar.wl @@ -35,19 +35,28 @@ makeChatCloudDockedCellContents // beginDefinition; makeChatCloudDockedCellContents[ ] := Block[ { $preferencesScope := EvaluationNotebook[ ] }, - Grid[ - { + DynamicWrapper[ + Grid[ { - Item[ $cloudChatBanner, Alignment -> Left ], - Item[ "", ItemSize -> Fit ], - makePersonaSelector[ ], - makeModelSelector[ ] - } - }, - Dividers -> { { False, False, False, True }, False }, - Spacings -> { 2, 0 }, - BaseStyle -> { "Text", FontSize -> 14, FontColor -> GrayLevel[ 0.4 ] }, - FrameStyle -> Directive[ Thickness[ 2 ], GrayLevel[ 0.9 ] ] + { + Item[ $cloudChatBanner, Alignment -> Left ], + Item[ "", ItemSize -> Fit ], + makePersonaSelector[ ], + makeModelSelector[ ] + } + }, + Alignment -> { Left, Baseline }, + Dividers -> { { False, False, False, True }, False }, + Spacings -> { 2, 0 }, + BaseStyle -> { "Text", FontSize -> 14, FontColor -> GrayLevel[ 0.4 ] }, + FrameStyle -> Directive[ Thickness[ 2 ], GrayLevel[ 0.9 ] ] + ], + Needs[ "GeneralUtilities`" -> None ]; + CurrentValue[ EvaluationNotebook[ ], TaggingRules ] = + GeneralUtilities`ToAssociations @ Replace[ + CurrentValue[ EvaluationNotebook[ ], TaggingRules ], + Except[ KeyValuePattern @ { } ] :> <| |> + ] ] ]; From 05d56aa1d3ca6f95e343b2b01745442d547146e4 Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Thu, 14 Dec 2023 10:50:35 -0500 Subject: [PATCH 37/50] Don't display model icons in cloud toolbar due to bad vertical alignment --- Source/Chatbook/PreferencesContent.wl | 9 +++++++-- 1 file changed, 7 insertions(+), 2 deletions(-) diff --git a/Source/Chatbook/PreferencesContent.wl b/Source/Chatbook/PreferencesContent.wl index c95aefd8..0a87d21e 100644 --- a/Source/Chatbook/PreferencesContent.wl +++ b/Source/Chatbook/PreferencesContent.wl @@ -596,7 +596,9 @@ makeModelNameSelector[ ], modelSelectCallback[ Dynamic @ service, Dynamic @ model ] ], - Map[ popupValue[ #[ "Name" ], #[ "DisplayName" ], #[ "Icon" ] ] &, models ], + Block[ { $noIcons = TrueQ @ $cloudNotebooks }, + Map[ popupValue[ #[ "Name" ], #[ "DisplayName" ], #[ "Icon" ] ] &, models ] + ], ImageSize -> Automatic ] ] @@ -1348,7 +1350,10 @@ popupValue[ value_String, label: Except[ $$unspecified ] ] := value -> label; popupValue[ value_String, label: Except[ $$unspecified ], icon: Except[ $$unspecified ] ] := - value -> Row[ { resizeMenuIcon @ inlineTemplateBoxes @ icon, label }, Spacer[ 1 ] ]; + If[ TrueQ @ $noIcons, + value -> label, + value -> Row[ { resizeMenuIcon @ inlineTemplateBoxes @ icon, label }, Spacer[ 1 ] ] + ]; popupValue // endDefinition; From a2c7fe2d1bc84c19fde6794bd4e74164e179ad7c Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Thu, 14 Dec 2023 19:15:15 -0500 Subject: [PATCH 38/50] Update the cloud toolbar to handle multiple services --- PacletInfo.wl | 2 +- Source/Chatbook/CloudToolbar.wl | 111 +++++++++++++++++++++++++- Source/Chatbook/PreferencesContent.wl | 10 ++- Source/Chatbook/Prompting.wl | 3 +- Source/Chatbook/Sandbox.wl | 2 +- 5 files changed, 123 insertions(+), 5 deletions(-) diff --git a/PacletInfo.wl b/PacletInfo.wl index 304048e8..eed7161c 100644 --- a/PacletInfo.wl +++ b/PacletInfo.wl @@ -2,7 +2,7 @@ PacletObject[ <| "Name" -> "Wolfram/Chatbook", "PublisherID" -> "Wolfram", "Version" -> "1.3.4", - "WolframVersion" -> "13.3+", + "WolframVersion" -> "14.0+", "Description" -> "Wolfram Notebooks + LLMs", "License" -> "MIT", "Creator" -> "Connor Gray, Theodore Gray, Richard Hennigan", diff --git a/Source/Chatbook/CloudToolbar.wl b/Source/Chatbook/CloudToolbar.wl index d6705bce..b33a91ab 100644 --- a/Source/Chatbook/CloudToolbar.wl +++ b/Source/Chatbook/CloudToolbar.wl @@ -13,6 +13,7 @@ Needs[ "Wolfram`Chatbook`Common`" ]; Needs[ "Wolfram`Chatbook`Dialogs`" ]; Needs[ "Wolfram`Chatbook`Dynamics`" ]; Needs[ "Wolfram`Chatbook`PreferencesContent`" ]; +Needs[ "Wolfram`Chatbook`Services`" ]; (* ::**************************************************************************************************************:: *) (* ::Section::Closed:: *) @@ -42,7 +43,7 @@ makeChatCloudDockedCellContents[ ] := Item[ $cloudChatBanner, Alignment -> Left ], Item[ "", ItemSize -> Fit ], makePersonaSelector[ ], - makeModelSelector[ ] + cloudModelSelector[ ] } }, Alignment -> { Left, Baseline }, @@ -62,6 +63,114 @@ makeChatCloudDockedCellContents[ ] := makeChatCloudDockedCellContents // endDefinition; +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*cloudModelSelector*) +cloudModelSelector // beginDefinition; + +cloudModelSelector[ ] := + DynamicModule[ { serviceSelector, modelSelector }, + + serviceSelector = PopupMenu[ + Dynamic[ + Replace[ + CurrentValue[ EvaluationNotebook[ ], { TaggingRules, "ChatNotebookSettings", "Model" } ], + { + _String|Inherited :> "OpenAI", + KeyValuePattern[ "Service" -> service_String ] :> service, + _ :> Set[ + CurrentValue[ + EvaluationNotebook[ ], + { TaggingRules, "ChatNotebookSettings", "Model" } + ], + $DefaultModel + ][ "Service" ] + } + ], + Function[ + CurrentValue[ + EvaluationNotebook[ ], + { TaggingRules, "ChatNotebookSettings", "Model", "Service" } + ] = #1; + + CurrentValue[ + EvaluationNotebook[ ], + { TaggingRules, "ChatNotebookSettings", "Model", "Name" } + ] = Automatic; + + cloudModelNameSelector[ Dynamic @ modelSelector, #1 ] + ] + ], + KeyValueMap[ + #1 -> Row @ { inlineTemplateBoxes[ #2[ "Icon" ] ], Spacer[ 1 ], #2[ "Service" ] } &, + $availableServices + ] + ]; + + cloudModelNameSelector[ + Dynamic @ modelSelector, + Replace[ + CurrentValue[ EvaluationNotebook[ ], { TaggingRules, "ChatNotebookSettings", "Model" } ], + { + _String|Inherited :> "OpenAI", + KeyValuePattern[ "Service" -> service_String ] :> service, + _ :> Set[ + CurrentValue[ EvaluationNotebook[ ], { TaggingRules, "ChatNotebookSettings", "Model" } ], + $DefaultModel + ][ "Service" ] + } + ] + ]; + + Row @ { + "LLM Service: ", serviceSelector, + Spacer[ 5 ], + "Model: ", Dynamic @ modelSelector + } + ]; + +cloudModelSelector // endDefinition; + +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*cloudModelNameSelector*) +cloudModelNameSelector // beginDefinition; + +cloudModelNameSelector[ Dynamic[ modelSelector_ ], service_String ] := + modelSelector = DynamicModule[ { display, models }, + display = ProgressIndicator[ Appearance -> "Percolate" ]; + Dynamic[ display ], + Initialization :> ( + models = getServiceModelList @ service; + If[ SameQ[ + CurrentValue[ EvaluationNotebook[ ], { TaggingRules, "ChatNotebookSettings", "Model", "Name" } ], + Automatic + ], + CurrentValue[ EvaluationNotebook[ ], { TaggingRules, "ChatNotebookSettings", "Model", "Name" } ] = + First[ models, <| "Name" -> Automatic |> ][ "Name" ] + ]; + + display = PopupMenu[ + Dynamic[ + Replace[ + CurrentChatSettings[ EvaluationNotebook[ ], "Model" ], + { KeyValuePattern[ "Name" -> model_String ] :> model, _ :> Automatic } + ], + Function[ + CurrentValue[ + EvaluationNotebook[ ], + { TaggingRules, "ChatNotebookSettings", "Model", "Name" } + ] = #1 + ] + ], + (#Name -> #DisplayName &) /@ models + ] + ), + SynchronousInitialization -> False + ]; + +cloudModelNameSelector // endDefinition; + (* ::**************************************************************************************************************:: *) (* ::Section::Closed:: *) (*Notebook Type Label*) diff --git a/Source/Chatbook/PreferencesContent.wl b/Source/Chatbook/PreferencesContent.wl index 0a87d21e..82602f51 100644 --- a/Source/Chatbook/PreferencesContent.wl +++ b/Source/Chatbook/PreferencesContent.wl @@ -363,7 +363,15 @@ makePersonaSelector0[ personas: { (_String -> _).. } ] := "Persona:", Spacer[ 3 ], PopupMenu[ - scopedDynamic @ CurrentChatSettings[ $preferencesScope, "LLMEvaluator" ], + scopedDynamic[ + CurrentChatSettings[ $preferencesScope, "LLMEvaluator" ], + Function[ + CurrentValue[ + $preferencesScope, + { TaggingRules, "ChatNotebookSettings", "LLMEvaluator" } + ] = #1 + ] + ], personas ] }, diff --git a/Source/Chatbook/Prompting.wl b/Source/Chatbook/Prompting.wl index 7b81f476..f25f4ec6 100644 --- a/Source/Chatbook/Prompting.wl +++ b/Source/Chatbook/Prompting.wl @@ -170,7 +170,8 @@ becomes ``Styled message``."; $basePromptComponents[ "SpecialURI" ] = "\ * You will occasionally see markdown links with special URI schemes, e.g. ![label](scheme://content-id) that represent \ -interactive interface elements. You can use these in your responses to display the same elements to the user."; +interactive interface elements. You can use these in your responses to display the same elements to the user, but they \ +must be formatted as image links (include the '!' at the beginning). If you do not include the '!', the link will fail."; $basePromptComponents[ "SpecialURIAudio" ] = "\ * ![label](audio://content-id) represents an interactive audio player."; diff --git a/Source/Chatbook/Sandbox.wl b/Source/Chatbook/Sandbox.wl index 954bc983..3fa1f771 100644 --- a/Source/Chatbook/Sandbox.wl +++ b/Source/Chatbook/Sandbox.wl @@ -432,7 +432,7 @@ initializeExpressions[ flat: HoldComplete @ Association @ OrderlessPatternSequen ReplacePart[ flat, Thread[ pos -> Extract[ flat, pos ] ] ] ]; -initializeExpressions[ failed: HoldComplete[ _Failure ] ] := +initializeExpressions[ failed: HoldComplete[ _Failure|$Failed|$Aborted ] ] := failed; initializeExpressions // endDefinition; From 470118ff4e4c3922ce287c36dfeda7b66cb879b0 Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Thu, 14 Dec 2023 19:24:10 -0500 Subject: [PATCH 39/50] Update definition notebook with version requirement --- ResourceDefinition.nb | 34 +++++++++++++++++----------------- 1 file changed, 17 insertions(+), 17 deletions(-) diff --git a/ResourceDefinition.nb b/ResourceDefinition.nb index 3e1f6ed0..3ec222ca 100644 --- a/ResourceDefinition.nb +++ b/ResourceDefinition.nb @@ -11344,7 +11344,7 @@ Notebook[ {0, 255}, ColorFunction -> RGBColor, ImageResolution -> {72.0, 72.0}, - SmoothingQuality -> "High" + RasterInterpolation -> "High" ], BoxForm`ImageTag[ "Byte", @@ -12035,7 +12035,7 @@ Notebook[ {0, 255}, ColorFunction -> RGBColor, ImageResolution -> {144.0, 144.0}, - SmoothingQuality -> "High" + RasterInterpolation -> "High" ], BoxForm`ImageTag[ "Byte", @@ -12091,7 +12091,7 @@ Notebook[ {0, 255}, ColorFunction -> RGBColor, ImageResolution -> {144.0, 144.0}, - SmoothingQuality -> "High" + RasterInterpolation -> "High" ], BoxForm`ImageTag[ "Byte", @@ -12128,7 +12128,7 @@ Notebook[ {0, 255}, ColorFunction -> RGBColor, ImageResolution -> {144.0, 144.0}, - SmoothingQuality -> "High" + RasterInterpolation -> "High" ], BoxForm`ImageTag[ "Byte", @@ -12165,7 +12165,7 @@ Notebook[ {0, 255}, ColorFunction -> RGBColor, ImageResolution -> {144.0, 144.0}, - SmoothingQuality -> "High" + RasterInterpolation -> "High" ], BoxForm`ImageTag[ "Byte", @@ -12230,7 +12230,7 @@ Notebook[ {0, 255}, ColorFunction -> RGBColor, ImageResolution -> {144.0, 144.0}, - SmoothingQuality -> "High" + RasterInterpolation -> "High" ], BoxForm`ImageTag[ "Byte", @@ -12267,7 +12267,7 @@ Notebook[ {0, 255}, ColorFunction -> RGBColor, ImageResolution -> {144.0, 144.0}, - SmoothingQuality -> "High" + RasterInterpolation -> "High" ], BoxForm`ImageTag[ "Byte", @@ -12304,7 +12304,7 @@ Notebook[ {0, 255}, ColorFunction -> RGBColor, ImageResolution -> {144.0, 144.0}, - SmoothingQuality -> "High" + RasterInterpolation -> "High" ], BoxForm`ImageTag[ "Byte", @@ -12353,7 +12353,7 @@ Notebook[ {0, 255}, ColorFunction -> RGBColor, ImageResolution -> {144.0, 144.0}, - SmoothingQuality -> "High" + RasterInterpolation -> "High" ], BoxForm`ImageTag[ "Byte", @@ -12390,7 +12390,7 @@ Notebook[ {0, 255}, ColorFunction -> RGBColor, ImageResolution -> {144.0, 144.0}, - SmoothingQuality -> "High" + RasterInterpolation -> "High" ], BoxForm`ImageTag[ "Byte", @@ -12433,7 +12433,7 @@ Notebook[ {0, 255}, ColorFunction -> RGBColor, ImageResolution -> {144.0, 144.0}, - SmoothingQuality -> "High" + RasterInterpolation -> "High" ], BoxForm`ImageTag[ "Byte", @@ -14048,7 +14048,7 @@ Notebook[ }, CellID -> 267876551 ], - Cell["13.3+", "Text", CellID -> 1052559837] + Cell["14.0+", "Text", CellID -> 1052559837] }, Open ] @@ -17501,7 +17501,7 @@ Notebook[ "Default" -> Image[ CompressedData[ - "\n\n1:eJxTTMoPSmNiYGAo5gASQYnljkVFiZXBAkBOaF5xZnpeaopnXklqemqRRRIz\nUFAcikHs/4QAMWqA4ANlAJchNy8+3Lv6/OKOvT2Z6yAIyAaKAMWJMeTN67cb\nZx9riFyGCwFlgWrwGHL32pNJhZuAKtsSV+1ZfuH66ccf336FICAbKAIUB8oC\n1QBVYjUEaD7EhAXNe96/+oI19IDiQFmIOXD3IBsC8QVQDcGIgJgDVI9mCDDE\nIL7A5QY090D8BQlnuCHAkAcKAn1N0AQIAKoEqgfqQjYEGINAQWDoEWkIUCVQ\nPVAXUC8kNQIZwJQAFATGApGGAFUC1QN1QQwBAsoNoYpL/lMvTKgSO1RJJ1RJ\nsdTKO1TJxdQqT+CAwpKNDEAwIv4TV9oDAHfUai0=\n " + "\n1:eJxTTMoPSmNiYGAo5gASQYnljkVFiZXBAkBOaF5xZnpeaopnXklqemqRRRIz\nUFAcikHs/4QAMWqA4ANlAJchNy8+3Lv6/OKOvT2Z6yAIyAaKAMWJMeTN67cb\nZx9riFyGCwFlgWrwGHL32pNJhZuAKtsSV+1ZfuH66ccf336FICAbKAIUB8oC\n1QBVYjUEaD7EhAXNe96/+oI19IDiQFmIOXD3IBsC8QVQDcGIgJgDVI9mCDDE\nIL7A5QY090D8BQlnuCHAkAcKAn1N0AQIAKoEqgfqQjYEGINAQWDoEWkIUCVQ\nPVAXUC8kNQIZwJQAFATGApGGAFUC1QN1QQwBAsoNoYpL/lMvTKgSO1RJJ1RJ\nsdTKO1TJxdQqT+CAwpKNDEAwIv4TV9oDAHfUai0=\n " ], "Byte", ColorSpace -> "RGB", @@ -17862,7 +17862,7 @@ Notebook[ "Default" -> Image[ CompressedData[ - "\n\n1:eJxTTMoPSmNiYGAo5gASQYnljkVFiZXBAkBOaF5xZnpeaopnXklqemqRRRIz\nUFAcikHs/4QAMWqA4ANlAJchNy8+3Lv6/OKOvT2Z6yAIyAaKAMWJMeTN67cb\nZx9riFyGCwFlgWrwGHL32pNJhZuAKtsSV+1ZfuH66ccf336FICAbKAIUB8oC\n1QBVYjUEaD7EhAXNe96/+oI19IDiQFmIOXD3IBsC8QVQDcGIgJgDVI9mCDDE\nIL7A5QY090D8BQlnuCHAkAcKAn1N0AQIAKoEqgfqQjYEGINAQWDoEWkIUCVQ\nPVAXUC8kNQIZwJQAFATGApGGAFUC1QN1QQwBAsoNoYpL/lMvTKgSO1RJJ1RJ\nsdTKO1TJxdQqT+CAwpKNDEAwIv4TV9oDAHfUai0=\n " + "\n1:eJxTTMoPSmNiYGAo5gASQYnljkVFiZXBAkBOaF5xZnpeaopnXklqemqRRRIz\nUFAcikHs/4QAMWqA4ANlAJchNy8+3Lv6/OKOvT2Z6yAIyAaKAMWJMeTN67cb\nZx9riFyGCwFlgWrwGHL32pNJhZuAKtsSV+1ZfuH66ccf336FICAbKAIUB8oC\n1QBVYjUEaD7EhAXNe96/+oI19IDiQFmIOXD3IBsC8QVQDcGIgJgDVI9mCDDE\nIL7A5QY090D8BQlnuCHAkAcKAn1N0AQIAKoEqgfqQjYEGINAQWDoEWkIUCVQ\nPVAXUC8kNQIZwJQAFATGApGGAFUC1QN1QQwBAsoNoYpL/lMvTKgSO1RJJ1RJ\nsdTKO1TJxdQqT+CAwpKNDEAwIv4TV9oDAHfUai0=\n " ], "Byte", ColorSpace -> "RGB", @@ -18129,7 +18129,7 @@ Notebook[ "Default" -> Image[ CompressedData[ - "\n\n1:eJxTTMoPSmNiYGAo5gASQYnljkVFiZXBAkBOaF5xZnpeaopnXklqemqRRRIz\nUFAcikHs/4QAMWqA4ANlAJchNy8+3Lv6/OKOvT2Z6yAIyAaKAMWJMeTN67cb\nZx9riFyGCwFlgWrwGHL32pNJhZuAKtsSV+1ZfuH66ccf336FICAbKAIUB8oC\n1QBVYjUEaD7EhAXNe96/+oI19IDiQFmIOXD3IBsC8QVQDcGIgJgDVI9mCDDE\nIL7A5QY090D8BQlnuCHAkAcKAn1N0AQIAKoEqgfqQjYEGINAQWDoEWkIUCVQ\nPVAXUC8kNQIZwJQAFATGApGGAFUC1QN1QQwBAsoNoYpL/lMvTKgSO1RJJ1RJ\nsdTKO1TJxdQqT+CAwpKNDEAwIv4TV9oDAHfUai0=\n " + "\n1:eJxTTMoPSmNiYGAo5gASQYnljkVFiZXBAkBOaF5xZnpeaopnXklqemqRRRIz\nUFAcikHs/4QAMWqA4ANlAJchNy8+3Lv6/OKOvT2Z6yAIyAaKAMWJMeTN67cb\nZx9riFyGCwFlgWrwGHL32pNJhZuAKtsSV+1ZfuH66ccf336FICAbKAIUB8oC\n1QBVYjUEaD7EhAXNe96/+oI19IDiQFmIOXD3IBsC8QVQDcGIgJgDVI9mCDDE\nIL7A5QY090D8BQlnuCHAkAcKAn1N0AQIAKoEqgfqQjYEGINAQWDoEWkIUCVQ\nPVAXUC8kNQIZwJQAFATGApGGAFUC1QN1QQwBAsoNoYpL/lMvTKgSO1RJJ1RJ\nsdTKO1TJxdQqT+CAwpKNDEAwIv4TV9oDAHfUai0=\n " ], "Byte", ColorSpace -> "RGB", @@ -23971,7 +23971,7 @@ Notebook[ {11.8717, 7.94746} }, CompressedData[ - "\n\n1:eJxlkXtMU3cUx6soT4V7y6MV6QOYj97LvZUFWAdGv0EkmJkNyibo8LkRO8qs\nDzYsCr7oWHRCFUQRplINtloxomFqRAU6FohjAXEK69RKwaLjNcwgxamXGNkf\nO8nJySe/nOT8vp/gDRpl+lQej6fgemK+rQVI9GlzeMfycfKZvtxWK0dtIH80\nNYfEvzdMCbokOV5qkw95dhPoG95R/srKoqm9gDUWEbB5FZv2JrFYE3/J2k4R\n+LZwSufzOgZCh6/28Asf7Jz+VZNBxmBzb8q23TwCjk6zM+1gGBR3/7lo5t4F\ne4NKFozQyBMpNsYtI6C1+7ieUNMwDLjou+wEZOur+tf2UWgdeTxgziXx5FzN\n4P7dFOx+ouaetXykGiN/jVlEQWpp9YvW+MJquONa9kIGe1dieOtJP+jVS35W\n/CbD4Tj56dQBf0Q9Hml0b5PhiT2vwADBJNdYXFqqKoQw1UfMkNTLcFN/78KJ\n4kBIZywcFXtTMFz5YKwhPwjH50zJyDBR2J/5dNxEilHp9ezz3jgafJ/55VvT\nJcgYT1lx/L0wfNNYu7RsphSeOndFvieDLZ91Zi/lSaEuuDVXbWEwsZblIUVa\n4qP3z+5gEdWu1MYYJDjoOhSQQMgRcew7W2iDGD9+xG0elWPh1Rj1T3+KMF3f\nZWnu5/xc4QQdC8I7fxVfb1r+iWI2XnVs75s7zE7y1dWq6rsPWGRZZSKzRAQu\ntcVnXjNwrs8fUu0Tw8291zHsxaCB+zaZLEYIcfG5IDMMvztDKpmNYhi7w12O\ntNHIQWcJbRVhRc0XoYSGhnnagcayR0G4vu9BWawb/TbPU7NRpywNLrxH4ctz\n6z5VzgvEhJ6PbRTSrPEu288LJ1lVOs1oShdgT8vY6Kz7FCjhkQ4Phz+aJVzg\n3jTEiVE9nho/bFUd6t+5i0ZtlfYXWbQvbqRcWD7WQ+NM6LWXBRF8/HGWO1AX\nBktReDZTSSLn+/hsgmbg0MQGT60moWtV/8XXMXAviipMPU8iq3286f5DBkbl\nZbdV9SROZbb4P4xkEd2X260eJCEt/qFCl8si31n64eoAPlY+FerrbrJwclpL\nNvDRcHvboO1vFiUJhqNJd/7jvMWRa64vC0B6cvUQK2D+xx0eqpDMMcGkr3f8\nBvidex8=\n " + "\n1:eJxlkXtMU3cUx6soT4V7y6MV6QOYj97LvZUFWAdGv0EkmJkNyibo8LkRO8qs\nDzYsCr7oWHRCFUQRplINtloxomFqRAU6FohjAXEK69RKwaLjNcwgxamXGNkf\nO8nJySe/nOT8vp/gDRpl+lQej6fgemK+rQVI9GlzeMfycfKZvtxWK0dtIH80\nNYfEvzdMCbokOV5qkw95dhPoG95R/srKoqm9gDUWEbB5FZv2JrFYE3/J2k4R\n+LZwSufzOgZCh6/28Asf7Jz+VZNBxmBzb8q23TwCjk6zM+1gGBR3/7lo5t4F\ne4NKFozQyBMpNsYtI6C1+7ieUNMwDLjou+wEZOur+tf2UWgdeTxgziXx5FzN\n4P7dFOx+ouaetXykGiN/jVlEQWpp9YvW+MJquONa9kIGe1dieOtJP+jVS35W\n/CbD4Tj56dQBf0Q9Hml0b5PhiT2vwADBJNdYXFqqKoQw1UfMkNTLcFN/78KJ\n4kBIZywcFXtTMFz5YKwhPwjH50zJyDBR2J/5dNxEilHp9ezz3jgafJ/55VvT\nJcgYT1lx/L0wfNNYu7RsphSeOndFvieDLZ91Zi/lSaEuuDVXbWEwsZblIUVa\n4qP3z+5gEdWu1MYYJDjoOhSQQMgRcew7W2iDGD9+xG0elWPh1Rj1T3+KMF3f\nZWnu5/xc4QQdC8I7fxVfb1r+iWI2XnVs75s7zE7y1dWq6rsPWGRZZSKzRAQu\ntcVnXjNwrs8fUu0Tw8291zHsxaCB+zaZLEYIcfG5IDMMvztDKpmNYhi7w12O\ntNHIQWcJbRVhRc0XoYSGhnnagcayR0G4vu9BWawb/TbPU7NRpywNLrxH4ctz\n6z5VzgvEhJ6PbRTSrPEu288LJ1lVOs1oShdgT8vY6Kz7FCjhkQ4Phz+aJVzg\n3jTEiVE9nho/bFUd6t+5i0ZtlfYXWbQvbqRcWD7WQ+NM6LWXBRF8/HGWO1AX\nBktReDZTSSLn+/hsgmbg0MQGT60moWtV/8XXMXAviipMPU8iq3286f5DBkbl\nZbdV9SROZbb4P4xkEd2X260eJCEt/qFCl8si31n64eoAPlY+FerrbrJwclpL\nNvDRcHvboO1vFiUJhqNJd/7jvMWRa64vC0B6cvUQK2D+xx0eqpDMMcGkr3f8\nBvidex8=\n " ] } ] @@ -26561,7 +26561,7 @@ Notebook[ {6.81, 13.0} }, CompressedData[ - "\n\n1:eJxTTMoPSmViYGCQB2IQbct1fXGBrbRD6+vAHXKtvA7r3B9WiayTdoCI8zgc\n/qoR039IHkoLOjCAgYKDB0iZu4CDPFijgsOsmSDAC1UnCzWPE0rLQMXZHV6x\nmAia1Ug56E1Y8MMwjdXh685bXX9VJRx4Jq9sCvRkcTh7BgREHfoPgTSwOAQB\ndb8OFHYAO4eLFeo+IQcRMIMLzoe4h9dBW2LqFc4MYYd4zdMCx38JOviYdzom\npIo4PJgjuHSvo6jDkgKQz0QdCsEelHDQjAHZJAa1VxIqLwH3Jzofok8S4i9W\nRQews67LQsJhnoKDMRjIQ9Q3wMJJwQFMJULDSRJmrhzUPKh6Blmof+QcwM6K\nkXb4Bgq2rzJQcXFovMhA5UUdciqqluo0SztsKMqY+NZG2OHV1E08hTrSDquA\noTmXQdABPX4BaWq/EA==\n " + "\n1:eJxTTMoPSmViYGCQB2IQbct1fXGBrbRD6+vAHXKtvA7r3B9WiayTdoCI8zgc\n/qoR039IHkoLOjCAgYKDB0iZu4CDPFijgsOsmSDAC1UnCzWPE0rLQMXZHV6x\nmAia1Ug56E1Y8MMwjdXh685bXX9VJRx4Jq9sCvRkcTh7BgREHfoPgTSwOAQB\ndb8OFHYAO4eLFeo+IQcRMIMLzoe4h9dBW2LqFc4MYYd4zdMCx38JOviYdzom\npIo4PJgjuHSvo6jDkgKQz0QdCsEelHDQjAHZJAa1VxIqLwH3Jzofok8S4i9W\nRQews67LQsJhnoKDMRjIQ9Q3wMJJwQFMJULDSRJmrhzUPKh6Blmof+QcwM6K\nkXb4Bgq2rzJQcXFovMhA5UUdciqqluo0SztsKMqY+NZG2OHV1E08hTrSDquA\noTmXQdABPX4BaWq/EA==\n " ], { {8.81, 9.79}, From fd1d70eb5daddfa0617aad9dcb7c978ce578e573 Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Thu, 14 Dec 2023 19:28:29 -0500 Subject: [PATCH 40/50] Revert "Update definition notebook with version requirement" This reverts commit 470118ff4e4c3922ce287c36dfeda7b66cb879b0. --- ResourceDefinition.nb | 34 +++++++++++++++++----------------- 1 file changed, 17 insertions(+), 17 deletions(-) diff --git a/ResourceDefinition.nb b/ResourceDefinition.nb index 3ec222ca..3e1f6ed0 100644 --- a/ResourceDefinition.nb +++ b/ResourceDefinition.nb @@ -11344,7 +11344,7 @@ Notebook[ {0, 255}, ColorFunction -> RGBColor, ImageResolution -> {72.0, 72.0}, - RasterInterpolation -> "High" + SmoothingQuality -> "High" ], BoxForm`ImageTag[ "Byte", @@ -12035,7 +12035,7 @@ Notebook[ {0, 255}, ColorFunction -> RGBColor, ImageResolution -> {144.0, 144.0}, - RasterInterpolation -> "High" + SmoothingQuality -> "High" ], BoxForm`ImageTag[ "Byte", @@ -12091,7 +12091,7 @@ Notebook[ {0, 255}, ColorFunction -> RGBColor, ImageResolution -> {144.0, 144.0}, - RasterInterpolation -> "High" + SmoothingQuality -> "High" ], BoxForm`ImageTag[ "Byte", @@ -12128,7 +12128,7 @@ Notebook[ {0, 255}, ColorFunction -> RGBColor, ImageResolution -> {144.0, 144.0}, - RasterInterpolation -> "High" + SmoothingQuality -> "High" ], BoxForm`ImageTag[ "Byte", @@ -12165,7 +12165,7 @@ Notebook[ {0, 255}, ColorFunction -> RGBColor, ImageResolution -> {144.0, 144.0}, - RasterInterpolation -> "High" + SmoothingQuality -> "High" ], BoxForm`ImageTag[ "Byte", @@ -12230,7 +12230,7 @@ Notebook[ {0, 255}, ColorFunction -> RGBColor, ImageResolution -> {144.0, 144.0}, - RasterInterpolation -> "High" + SmoothingQuality -> "High" ], BoxForm`ImageTag[ "Byte", @@ -12267,7 +12267,7 @@ Notebook[ {0, 255}, ColorFunction -> RGBColor, ImageResolution -> {144.0, 144.0}, - RasterInterpolation -> "High" + SmoothingQuality -> "High" ], BoxForm`ImageTag[ "Byte", @@ -12304,7 +12304,7 @@ Notebook[ {0, 255}, ColorFunction -> RGBColor, ImageResolution -> {144.0, 144.0}, - RasterInterpolation -> "High" + SmoothingQuality -> "High" ], BoxForm`ImageTag[ "Byte", @@ -12353,7 +12353,7 @@ Notebook[ {0, 255}, ColorFunction -> RGBColor, ImageResolution -> {144.0, 144.0}, - RasterInterpolation -> "High" + SmoothingQuality -> "High" ], BoxForm`ImageTag[ "Byte", @@ -12390,7 +12390,7 @@ Notebook[ {0, 255}, ColorFunction -> RGBColor, ImageResolution -> {144.0, 144.0}, - RasterInterpolation -> "High" + SmoothingQuality -> "High" ], BoxForm`ImageTag[ "Byte", @@ -12433,7 +12433,7 @@ Notebook[ {0, 255}, ColorFunction -> RGBColor, ImageResolution -> {144.0, 144.0}, - RasterInterpolation -> "High" + SmoothingQuality -> "High" ], BoxForm`ImageTag[ "Byte", @@ -14048,7 +14048,7 @@ Notebook[ }, CellID -> 267876551 ], - Cell["14.0+", "Text", CellID -> 1052559837] + Cell["13.3+", "Text", CellID -> 1052559837] }, Open ] @@ -17501,7 +17501,7 @@ Notebook[ "Default" -> Image[ CompressedData[ - "\n1:eJxTTMoPSmNiYGAo5gASQYnljkVFiZXBAkBOaF5xZnpeaopnXklqemqRRRIz\nUFAcikHs/4QAMWqA4ANlAJchNy8+3Lv6/OKOvT2Z6yAIyAaKAMWJMeTN67cb\nZx9riFyGCwFlgWrwGHL32pNJhZuAKtsSV+1ZfuH66ccf336FICAbKAIUB8oC\n1QBVYjUEaD7EhAXNe96/+oI19IDiQFmIOXD3IBsC8QVQDcGIgJgDVI9mCDDE\nIL7A5QY090D8BQlnuCHAkAcKAn1N0AQIAKoEqgfqQjYEGINAQWDoEWkIUCVQ\nPVAXUC8kNQIZwJQAFATGApGGAFUC1QN1QQwBAsoNoYpL/lMvTKgSO1RJJ1RJ\nsdTKO1TJxdQqT+CAwpKNDEAwIv4TV9oDAHfUai0=\n " + "\n\n1:eJxTTMoPSmNiYGAo5gASQYnljkVFiZXBAkBOaF5xZnpeaopnXklqemqRRRIz\nUFAcikHs/4QAMWqA4ANlAJchNy8+3Lv6/OKOvT2Z6yAIyAaKAMWJMeTN67cb\nZx9riFyGCwFlgWrwGHL32pNJhZuAKtsSV+1ZfuH66ccf336FICAbKAIUB8oC\n1QBVYjUEaD7EhAXNe96/+oI19IDiQFmIOXD3IBsC8QVQDcGIgJgDVI9mCDDE\nIL7A5QY090D8BQlnuCHAkAcKAn1N0AQIAKoEqgfqQjYEGINAQWDoEWkIUCVQ\nPVAXUC8kNQIZwJQAFATGApGGAFUC1QN1QQwBAsoNoYpL/lMvTKgSO1RJJ1RJ\nsdTKO1TJxdQqT+CAwpKNDEAwIv4TV9oDAHfUai0=\n " ], "Byte", ColorSpace -> "RGB", @@ -17862,7 +17862,7 @@ Notebook[ "Default" -> Image[ CompressedData[ - "\n1:eJxTTMoPSmNiYGAo5gASQYnljkVFiZXBAkBOaF5xZnpeaopnXklqemqRRRIz\nUFAcikHs/4QAMWqA4ANlAJchNy8+3Lv6/OKOvT2Z6yAIyAaKAMWJMeTN67cb\nZx9riFyGCwFlgWrwGHL32pNJhZuAKtsSV+1ZfuH66ccf336FICAbKAIUB8oC\n1QBVYjUEaD7EhAXNe96/+oI19IDiQFmIOXD3IBsC8QVQDcGIgJgDVI9mCDDE\nIL7A5QY090D8BQlnuCHAkAcKAn1N0AQIAKoEqgfqQjYEGINAQWDoEWkIUCVQ\nPVAXUC8kNQIZwJQAFATGApGGAFUC1QN1QQwBAsoNoYpL/lMvTKgSO1RJJ1RJ\nsdTKO1TJxdQqT+CAwpKNDEAwIv4TV9oDAHfUai0=\n " + "\n\n1:eJxTTMoPSmNiYGAo5gASQYnljkVFiZXBAkBOaF5xZnpeaopnXklqemqRRRIz\nUFAcikHs/4QAMWqA4ANlAJchNy8+3Lv6/OKOvT2Z6yAIyAaKAMWJMeTN67cb\nZx9riFyGCwFlgWrwGHL32pNJhZuAKtsSV+1ZfuH66ccf336FICAbKAIUB8oC\n1QBVYjUEaD7EhAXNe96/+oI19IDiQFmIOXD3IBsC8QVQDcGIgJgDVI9mCDDE\nIL7A5QY090D8BQlnuCHAkAcKAn1N0AQIAKoEqgfqQjYEGINAQWDoEWkIUCVQ\nPVAXUC8kNQIZwJQAFATGApGGAFUC1QN1QQwBAsoNoYpL/lMvTKgSO1RJJ1RJ\nsdTKO1TJxdQqT+CAwpKNDEAwIv4TV9oDAHfUai0=\n " ], "Byte", ColorSpace -> "RGB", @@ -18129,7 +18129,7 @@ Notebook[ "Default" -> Image[ CompressedData[ - "\n1:eJxTTMoPSmNiYGAo5gASQYnljkVFiZXBAkBOaF5xZnpeaopnXklqemqRRRIz\nUFAcikHs/4QAMWqA4ANlAJchNy8+3Lv6/OKOvT2Z6yAIyAaKAMWJMeTN67cb\nZx9riFyGCwFlgWrwGHL32pNJhZuAKtsSV+1ZfuH66ccf336FICAbKAIUB8oC\n1QBVYjUEaD7EhAXNe96/+oI19IDiQFmIOXD3IBsC8QVQDcGIgJgDVI9mCDDE\nIL7A5QY090D8BQlnuCHAkAcKAn1N0AQIAKoEqgfqQjYEGINAQWDoEWkIUCVQ\nPVAXUC8kNQIZwJQAFATGApGGAFUC1QN1QQwBAsoNoYpL/lMvTKgSO1RJJ1RJ\nsdTKO1TJxdQqT+CAwpKNDEAwIv4TV9oDAHfUai0=\n " + "\n\n1:eJxTTMoPSmNiYGAo5gASQYnljkVFiZXBAkBOaF5xZnpeaopnXklqemqRRRIz\nUFAcikHs/4QAMWqA4ANlAJchNy8+3Lv6/OKOvT2Z6yAIyAaKAMWJMeTN67cb\nZx9riFyGCwFlgWrwGHL32pNJhZuAKtsSV+1ZfuH66ccf336FICAbKAIUB8oC\n1QBVYjUEaD7EhAXNe96/+oI19IDiQFmIOXD3IBsC8QVQDcGIgJgDVI9mCDDE\nIL7A5QY090D8BQlnuCHAkAcKAn1N0AQIAKoEqgfqQjYEGINAQWDoEWkIUCVQ\nPVAXUC8kNQIZwJQAFATGApGGAFUC1QN1QQwBAsoNoYpL/lMvTKgSO1RJJ1RJ\nsdTKO1TJxdQqT+CAwpKNDEAwIv4TV9oDAHfUai0=\n " ], "Byte", ColorSpace -> "RGB", @@ -23971,7 +23971,7 @@ Notebook[ {11.8717, 7.94746} }, CompressedData[ - "\n1:eJxlkXtMU3cUx6soT4V7y6MV6QOYj97LvZUFWAdGv0EkmJkNyibo8LkRO8qs\nDzYsCr7oWHRCFUQRplINtloxomFqRAU6FohjAXEK69RKwaLjNcwgxamXGNkf\nO8nJySe/nOT8vp/gDRpl+lQej6fgemK+rQVI9GlzeMfycfKZvtxWK0dtIH80\nNYfEvzdMCbokOV5qkw95dhPoG95R/srKoqm9gDUWEbB5FZv2JrFYE3/J2k4R\n+LZwSufzOgZCh6/28Asf7Jz+VZNBxmBzb8q23TwCjk6zM+1gGBR3/7lo5t4F\ne4NKFozQyBMpNsYtI6C1+7ieUNMwDLjou+wEZOur+tf2UWgdeTxgziXx5FzN\n4P7dFOx+ouaetXykGiN/jVlEQWpp9YvW+MJquONa9kIGe1dieOtJP+jVS35W\n/CbD4Tj56dQBf0Q9Hml0b5PhiT2vwADBJNdYXFqqKoQw1UfMkNTLcFN/78KJ\n4kBIZywcFXtTMFz5YKwhPwjH50zJyDBR2J/5dNxEilHp9ezz3jgafJ/55VvT\nJcgYT1lx/L0wfNNYu7RsphSeOndFvieDLZ91Zi/lSaEuuDVXbWEwsZblIUVa\n4qP3z+5gEdWu1MYYJDjoOhSQQMgRcew7W2iDGD9+xG0elWPh1Rj1T3+KMF3f\nZWnu5/xc4QQdC8I7fxVfb1r+iWI2XnVs75s7zE7y1dWq6rsPWGRZZSKzRAQu\ntcVnXjNwrs8fUu0Tw8291zHsxaCB+zaZLEYIcfG5IDMMvztDKpmNYhi7w12O\ntNHIQWcJbRVhRc0XoYSGhnnagcayR0G4vu9BWawb/TbPU7NRpywNLrxH4ctz\n6z5VzgvEhJ6PbRTSrPEu288LJ1lVOs1oShdgT8vY6Kz7FCjhkQ4Phz+aJVzg\n3jTEiVE9nho/bFUd6t+5i0ZtlfYXWbQvbqRcWD7WQ+NM6LWXBRF8/HGWO1AX\nBktReDZTSSLn+/hsgmbg0MQGT60moWtV/8XXMXAviipMPU8iq3286f5DBkbl\nZbdV9SROZbb4P4xkEd2X260eJCEt/qFCl8si31n64eoAPlY+FerrbrJwclpL\nNvDRcHvboO1vFiUJhqNJd/7jvMWRa64vC0B6cvUQK2D+xx0eqpDMMcGkr3f8\nBvidex8=\n " + "\n\n1:eJxlkXtMU3cUx6soT4V7y6MV6QOYj97LvZUFWAdGv0EkmJkNyibo8LkRO8qs\nDzYsCr7oWHRCFUQRplINtloxomFqRAU6FohjAXEK69RKwaLjNcwgxamXGNkf\nO8nJySe/nOT8vp/gDRpl+lQej6fgemK+rQVI9GlzeMfycfKZvtxWK0dtIH80\nNYfEvzdMCbokOV5qkw95dhPoG95R/srKoqm9gDUWEbB5FZv2JrFYE3/J2k4R\n+LZwSufzOgZCh6/28Asf7Jz+VZNBxmBzb8q23TwCjk6zM+1gGBR3/7lo5t4F\ne4NKFozQyBMpNsYtI6C1+7ieUNMwDLjou+wEZOur+tf2UWgdeTxgziXx5FzN\n4P7dFOx+ouaetXykGiN/jVlEQWpp9YvW+MJquONa9kIGe1dieOtJP+jVS35W\n/CbD4Tj56dQBf0Q9Hml0b5PhiT2vwADBJNdYXFqqKoQw1UfMkNTLcFN/78KJ\n4kBIZywcFXtTMFz5YKwhPwjH50zJyDBR2J/5dNxEilHp9ezz3jgafJ/55VvT\nJcgYT1lx/L0wfNNYu7RsphSeOndFvieDLZ91Zi/lSaEuuDVXbWEwsZblIUVa\n4qP3z+5gEdWu1MYYJDjoOhSQQMgRcew7W2iDGD9+xG0elWPh1Rj1T3+KMF3f\nZWnu5/xc4QQdC8I7fxVfb1r+iWI2XnVs75s7zE7y1dWq6rsPWGRZZSKzRAQu\ntcVnXjNwrs8fUu0Tw8291zHsxaCB+zaZLEYIcfG5IDMMvztDKpmNYhi7w12O\ntNHIQWcJbRVhRc0XoYSGhnnagcayR0G4vu9BWawb/TbPU7NRpywNLrxH4ctz\n6z5VzgvEhJ6PbRTSrPEu288LJ1lVOs1oShdgT8vY6Kz7FCjhkQ4Phz+aJVzg\n3jTEiVE9nho/bFUd6t+5i0ZtlfYXWbQvbqRcWD7WQ+NM6LWXBRF8/HGWO1AX\nBktReDZTSSLn+/hsgmbg0MQGT60moWtV/8XXMXAviipMPU8iq3286f5DBkbl\nZbdV9SROZbb4P4xkEd2X260eJCEt/qFCl8si31n64eoAPlY+FerrbrJwclpL\nNvDRcHvboO1vFiUJhqNJd/7jvMWRa64vC0B6cvUQK2D+xx0eqpDMMcGkr3f8\nBvidex8=\n " ] } ] @@ -26561,7 +26561,7 @@ Notebook[ {6.81, 13.0} }, CompressedData[ - "\n1:eJxTTMoPSmViYGCQB2IQbct1fXGBrbRD6+vAHXKtvA7r3B9WiayTdoCI8zgc\n/qoR039IHkoLOjCAgYKDB0iZu4CDPFijgsOsmSDAC1UnCzWPE0rLQMXZHV6x\nmAia1Ug56E1Y8MMwjdXh685bXX9VJRx4Jq9sCvRkcTh7BgREHfoPgTSwOAQB\ndb8OFHYAO4eLFeo+IQcRMIMLzoe4h9dBW2LqFc4MYYd4zdMCx38JOviYdzom\npIo4PJgjuHSvo6jDkgKQz0QdCsEelHDQjAHZJAa1VxIqLwH3Jzofok8S4i9W\nRQews67LQsJhnoKDMRjIQ9Q3wMJJwQFMJULDSRJmrhzUPKh6Blmof+QcwM6K\nkXb4Bgq2rzJQcXFovMhA5UUdciqqluo0SztsKMqY+NZG2OHV1E08hTrSDquA\noTmXQdABPX4BaWq/EA==\n " + "\n\n1:eJxTTMoPSmViYGCQB2IQbct1fXGBrbRD6+vAHXKtvA7r3B9WiayTdoCI8zgc\n/qoR039IHkoLOjCAgYKDB0iZu4CDPFijgsOsmSDAC1UnCzWPE0rLQMXZHV6x\nmAia1Ug56E1Y8MMwjdXh685bXX9VJRx4Jq9sCvRkcTh7BgREHfoPgTSwOAQB\ndb8OFHYAO4eLFeo+IQcRMIMLzoe4h9dBW2LqFc4MYYd4zdMCx38JOviYdzom\npIo4PJgjuHSvo6jDkgKQz0QdCsEelHDQjAHZJAa1VxIqLwH3Jzofok8S4i9W\nRQews67LQsJhnoKDMRjIQ9Q3wMJJwQFMJULDSRJmrhzUPKh6Blmof+QcwM6K\nkXb4Bgq2rzJQcXFovMhA5UUdciqqluo0SztsKMqY+NZG2OHV1E08hTrSDquA\noTmXQdABPX4BaWq/EA==\n " ], { {8.81, 9.79}, From 4109ae33a18409015cb8ff71a6b252d69417b22e Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Thu, 14 Dec 2023 19:28:37 -0500 Subject: [PATCH 41/50] Increment paclet version --- PacletInfo.wl | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/PacletInfo.wl b/PacletInfo.wl index eed7161c..85858774 100644 --- a/PacletInfo.wl +++ b/PacletInfo.wl @@ -1,7 +1,7 @@ PacletObject[ <| "Name" -> "Wolfram/Chatbook", "PublisherID" -> "Wolfram", - "Version" -> "1.3.4", + "Version" -> "1.3.5", "WolframVersion" -> "14.0+", "Description" -> "Wolfram Notebooks + LLMs", "License" -> "MIT", From a9ec5f6885a5b11ce9b8e75e2014cfb1eda269a8 Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Thu, 14 Dec 2023 19:29:02 -0500 Subject: [PATCH 42/50] Revert version requirement --- PacletInfo.wl | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/PacletInfo.wl b/PacletInfo.wl index 85858774..fdf93604 100644 --- a/PacletInfo.wl +++ b/PacletInfo.wl @@ -2,7 +2,7 @@ PacletObject[ <| "Name" -> "Wolfram/Chatbook", "PublisherID" -> "Wolfram", "Version" -> "1.3.5", - "WolframVersion" -> "14.0+", + "WolframVersion" -> "13.3+", "Description" -> "Wolfram Notebooks + LLMs", "License" -> "MIT", "Creator" -> "Connor Gray, Theodore Gray, Richard Hennigan", From 9ba11989b5cef44ef2a5ffa147e15f5f8989314c Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Fri, 15 Dec 2023 12:30:11 -0500 Subject: [PATCH 43/50] Restored "OpenAIAPICompletionURL" preferences setting for 13.3 users --- Source/Chatbook/PreferencesContent.wl | 50 +++++++++++++++++++++++---- Source/Chatbook/SendChat.wl | 9 ++--- Source/Chatbook/Services.wl | 2 +- 3 files changed, 50 insertions(+), 11 deletions(-) diff --git a/Source/Chatbook/PreferencesContent.wl b/Source/Chatbook/PreferencesContent.wl index 82602f51..45771a8b 100644 --- a/Source/Chatbook/PreferencesContent.wl +++ b/Source/Chatbook/PreferencesContent.wl @@ -310,7 +310,7 @@ createNotebookSettingsPanel // endDefinition; makeDefaultSettingsContent // beginDefinition; makeDefaultSettingsContent[ ] := Enclose[ - Module[ { assistanceCheckbox, personaSelector, modelSelector, temperatureInput }, + Module[ { assistanceCheckbox, personaSelector, modelSelector, temperatureInput, openAICompletionURLInput }, (* Checkbox to enable automatic assistance for normal shift-enter evaluations: *) assistanceCheckbox = ConfirmMatch[ makeAssistanceCheckbox[ ], _Style, "AssistanceCheckbox" ]; (* The personaSelector is a pop-up menu for selecting the default persona: *) @@ -319,14 +319,21 @@ makeDefaultSettingsContent[ ] := Enclose[ modelSelector = ConfirmMatch[ makeModelSelector[ ], _Dynamic, "ModelSelector" ]; (* The temperatureInput is an input field for setting the default 'temperature' for responses: *) temperatureInput = ConfirmMatch[ makeTemperatureInput[ ], _Style, "TemperatureInput" ]; + (* The openAICompletionURLInput is an input field for setting URL used for API calls to OpenAI: *) + openAICompletionURLInput = ConfirmMatch[ + makeOpenAICompletionURLInput[ ], + _Style|Nothing, (* Returns Nothing if we're relying on LLMServices for API requests *) + "OpenAICompletionURLInput" + ]; (* Assemble the persona selector, model selector, and temperature slider into a grid layout: *) Grid[ - { - { assistanceCheckbox }, - { personaSelector }, - { modelSelector }, - { temperatureInput } + List /@ { + assistanceCheckbox, + personaSelector, + modelSelector, + temperatureInput, + openAICompletionURLInput }, Alignment -> { Left, Baseline }, Spacings -> { 0, 0.7 } @@ -749,6 +756,37 @@ makeTemperatureInput[ ] := highlightControl[ makeTemperatureInput // endDefinition; +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*makeOpenAICompletionURLInput*) +makeOpenAICompletionURLInput // beginDefinition; + +makeOpenAICompletionURLInput[ ] := + makeOpenAICompletionURLInput @ $useLLMServices; + +makeOpenAICompletionURLInput[ True ] := + Nothing; + +makeOpenAICompletionURLInput[ False ] := highlightControl[ + prefsInputField[ + "Chat Completion URL:", + scopedDynamic[ + (* cSpell: ignore AIAPI *) + CurrentChatSettings[ $preferencesScope, "OpenAIAPICompletionURL" ], + { + None, + If[ StringQ @ #, CurrentChatSettings[ $preferencesScope, "OpenAIAPICompletionURL" ] = # ] & + } + ], + String, + ImageSize -> { 200, Automatic } + ], + "Notebooks", + "OpenAIAPICompletionURL" +]; + +makeOpenAICompletionURLInput // endDefinition; + (* ::**************************************************************************************************************:: *) (* ::Subsection::Closed:: *) (*makeInterfaceContent*) diff --git a/Source/Chatbook/SendChat.wl b/Source/Chatbook/SendChat.wl index 305a0e3d..5249e805 100644 --- a/Source/Chatbook/SendChat.wl +++ b/Source/Chatbook/SendChat.wl @@ -300,12 +300,13 @@ sendChat // endDefinition; (*makeHTTPRequest*) makeHTTPRequest // beginDefinition; -(* cSpell: ignore ENDTOOLCALL *) +(* cSpell: ignore ENDTOOLCALL, AIAPI *) makeHTTPRequest[ settings_Association? AssociationQ, messages: { __Association } ] := - Enclose @ Module[ { key, stream, model, tokens, temperature, topP, freqPenalty, presPenalty, data, body, apiCompletionURL }, + Enclose @ Module[ + { key, stream, model, tokens, temperature, topP, freqPenalty, presPenalty, data, body, apiCompletionURL }, - key = ConfirmBy[ Lookup[ settings, "OpenAIKey" ], StringQ ]; - stream = True; + key = ConfirmBy[ Lookup[ settings, "OpenAIKey" ], StringQ ]; + stream = True; apiCompletionURL = ConfirmBy[ Lookup[ settings, "OpenAIAPICompletionURL" ], StringQ ]; (* model parameters *) diff --git a/Source/Chatbook/Services.wl b/Source/Chatbook/Services.wl index 62e29afc..b0d4a7e2 100644 --- a/Source/Chatbook/Services.wl +++ b/Source/Chatbook/Services.wl @@ -192,7 +192,7 @@ $availableServices := getAvailableServices[ ]; (*getAvailableServices*) getAvailableServices // beginDefinition; getAvailableServices[ ] := getAvailableServices @ $useLLMServices; -getAvailableServices[ False ] := $fallBackServices; +getAvailableServices[ False ] := getAvailableServices0 @ $fallBackServices; getAvailableServices[ True ] := getAvailableServices0[ ]; getAvailableServices // endDefinition; From a68dcc378611c67ed7a26707f9302a7bd719cc91 Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Fri, 15 Dec 2023 13:45:34 -0500 Subject: [PATCH 44/50] Bugfix: maintain attachment direction for nested menus and store the original root attached cell --- Source/Chatbook/Menus.wl | 77 +++++++++++++++++++++++++++++++++++----- Source/Chatbook/UI.wl | 6 ++-- 2 files changed, 72 insertions(+), 11 deletions(-) diff --git a/Source/Chatbook/Menus.wl b/Source/Chatbook/Menus.wl index ebe37c5c..39ea2b11 100644 --- a/Source/Chatbook/Menus.wl +++ b/Source/Chatbook/Menus.wl @@ -10,6 +10,7 @@ BeginPackage[ "Wolfram`Chatbook`Menus`" ]; (* :!CodeAnalysis::BeginBlock:: *) HoldComplete[ + `attachMenuCell; `AttachSubmenu; `MakeMenu; `menuMagnification; @@ -149,27 +150,43 @@ submenuLabel // endDefinition; (* ::**************************************************************************************************************:: *) (* ::Section::Closed:: *) (*AttachSubmenu*) +AttachSubmenu // beginDefinition; + AttachSubmenu[ parentMenu_, submenu: Cell[ __, "AttachedChatMenu", ___ ] ] := Enclose[ - Module[ { pos, oPos, offsetX, offsetY, magnification }, + Module[ { parentInfo, root, pos, oPos, offsetX, offsetY, magnification, tags, attached }, NotebookDelete @ Cells[ parentMenu, AttachedCell -> True, CellStyle -> "AttachedChatMenu" ]; - { pos, oPos } = ConfirmMatch[ determineAttachmentPosition[ ], { { _, _ }, { _, _ } }, "Position" ]; + + parentInfo = Replace[ + Association @ CurrentValue[ parentMenu, { TaggingRules, "MenuData" } ], + Except[ _? AssociationQ ] :> <| |> + ]; + + { pos, oPos } = ConfirmMatch[ determineAttachmentPosition @ parentInfo, { { _, _ }, { _, _ } }, "Position" ]; offsetX = If[ MatchQ[ pos, { Left, _ } ], -3, 3 ]; offsetY = If[ MatchQ[ pos, { _, Top } ], 5, -5 ]; magnification = Replace[ - AbsoluteCurrentValue[ parentMenu, Magnification ], + Lookup[ parentInfo, "Magnification", AbsoluteCurrentValue[ parentMenu, Magnification ] ], Except[ _? NumberQ ] :> If[ $OperatingSystem === "Windows", 0.75, 1 ] ]; - AttachCell[ + tags = <| "MenuData" -> <| parentInfo, "Magnification" -> magnification, "Position" -> { pos, oPos } |> |>; + + attached = AttachCell[ parentMenu, - Append[ submenu, Magnification -> magnification ], + Append[ submenu, Unevaluated @ Sequence[ Magnification -> magnification, TaggingRules -> tags ] ], pos, Offset[ { offsetX, offsetY }, { 0, 0 } ], oPos, RemovalConditions -> { "MouseClickOutside", "EvaluatorQuit" } - ] + ]; + + If[ ! MatchQ[ tags[ "MenuData", "Root" ], _CellObject ], + CurrentValue[ attached, { TaggingRules, "MenuData", "Root" } ] = attached; + ]; + + attached ], throwInternalFailure ]; @@ -183,6 +200,8 @@ AttachSubmenu[ parentMenu_, expr: Except[ _Cell ] ] := AttachSubmenu[ expr_ ] := AttachSubmenu[ EvaluationCell[ ], expr ]; +AttachSubmenu // endDefinition; + (* ::**************************************************************************************************************:: *) (* ::Subsection::Closed:: *) (*menuMagnification*) @@ -196,11 +215,21 @@ menuMagnification // endDefinition; (* ::Subsection::Closed:: *) (*determineAttachmentPosition*) determineAttachmentPosition // beginDefinition; -determineAttachmentPosition[ ] := determineAttachmentPosition @ MousePosition[ "WindowScaled" ]; -determineAttachmentPosition[ pos_List ] := determineAttachmentPosition[ pos, quadrant @ pos ]; -determineAttachmentPosition[ _, { h_, v_ } ] := { { Replace[ h, { Left -> Right, Right -> Left } ], v }, { h, Center } }; + +determineAttachmentPosition[ info_Association ] := + Lookup[ info, "Position", determineAttachmentPosition @ MousePosition[ "WindowScaled" ] ]; + +determineAttachmentPosition[ pos_List ] := + determineAttachmentPosition[ pos, quadrant @ pos ]; + +determineAttachmentPosition[ _, { h_, v_ } ] := + { { Replace[ h, { Left -> Right, Right -> Left } ], v }, { h, Center } }; + determineAttachmentPosition // endDefinition; +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*quadrant*) quadrant // beginDefinition; quadrant[ None ] := None; quadrant[ { x_? NumberQ, y_? NumberQ } ] := quadrant[ TrueQ[ x >= 0.5 ], TrueQ[ y >= 0.67 ] ]; @@ -212,9 +241,18 @@ quadrant // endDefinition; (* ::**************************************************************************************************************:: *) (* ::Section::Closed:: *) +(*Attaching and Removing Menus*) + +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) (*removeChatMenus*) removeChatMenus // beginDefinition; +removeChatMenus[ obj: $$feObj ] := + With[ { root = CurrentValue[ obj, { TaggingRules, "MenuData", "Root" } ] }, + NotebookDelete @ root /; MatchQ[ root, _CellObject ] + ]; + removeChatMenus[ box_BoxObject ] := removeChatMenus @ parentCell @ box; @@ -230,6 +268,27 @@ removeChatMenus[ $Failed ] := removeChatMenus // endDefinition; +(* ::**************************************************************************************************************:: *) +(* ::Subsection::Closed:: *) +(*attachMenuCell*) +attachMenuCell // beginDefinition; + +attachMenuCell[ parent: $$feObj, args___ ] := + Module[ { attached, root }, + attached = AttachCell[ parent, args ]; + + root = Replace[ + CurrentValue[ parent, { TaggingRules, "MenuData", "Root" } ], + Except[ _CellObject ] :> attached + ]; + + CurrentValue[ attached, { TaggingRules, "MenuData", "Root" } ] = root; + + attached + ]; + +attachMenuCell // endDefinition; + (* ::**************************************************************************************************************:: *) (* ::Section::Closed:: *) (*Package Footer*) diff --git a/Source/Chatbook/UI.wl b/Source/Chatbook/UI.wl index b6a94692..9e540648 100644 --- a/Source/Chatbook/UI.wl +++ b/Source/Chatbook/UI.wl @@ -87,6 +87,8 @@ CreateToolbarContent[] := With[{ CurrentValue[menuCell, {TaggingRules, "IsChatEnabled"}] = TrueQ[CurrentValue[nbObj, {StyleDefinitions, "ChatInput", Evaluatable}]]; + CurrentValue[menuCell, {TaggingRules, "MenuData", "Root"}] = menuCell; + PaneSelector[ { True :> ( @@ -441,7 +443,7 @@ MakeChatInputActiveCellDingbat[cell_CellObject] := Module[{ ContentPadding -> False ], ( - AttachCell[ + attachMenuCell[ EvaluationCell[], makeChatActionMenu[ "Input", @@ -533,7 +535,7 @@ MakeChatDelimiterCellDingbat[cell_CellObject] := Module[{ ContentPadding -> False ], ( - AttachCell[ + attachMenuCell[ EvaluationCell[], makeChatActionMenu[ "Delimiter", From 5df16d7a9c2c0f6275f753adc4df65c86b7f29ee Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Fri, 15 Dec 2023 13:46:30 -0500 Subject: [PATCH 45/50] Display a menu item to connect to service instead of popping up a dialog on mouseover --- Source/Chatbook/UI.wl | 59 ++++++++++++++++++++++++++++++++++++++----- 1 file changed, 52 insertions(+), 7 deletions(-) diff --git a/Source/Chatbook/UI.wl b/Source/Chatbook/UI.wl index 9e540648..073d38b2 100644 --- a/Source/Chatbook/UI.wl +++ b/Source/Chatbook/UI.wl @@ -955,7 +955,10 @@ $currentSelectionCheck = Style[ "\[Checkmark]", FontColor -> GrayLevel[ 0.25 ] ] dynamicModelMenu // beginDefinition; dynamicModelMenu[ obj_, root_, model_, service_? modelListCachedQ ] := - makeServiceModelMenu[ obj, root, model, service ]; + Module[ { display }, + makeServiceModelMenu[ Dynamic @ display, obj, root, model, service ]; + display + ]; dynamicModelMenu[ obj_, root_, model_, service_ ] := DynamicModule[ { display }, @@ -981,7 +984,7 @@ dynamicModelMenu[ obj_, root_, model_, service_ ] := Dynamic[ display, TrackedSymbols :> { display } ], Initialization :> Quiet[ Needs[ "Wolfram`Chatbook`" -> None ]; - display = catchAlways @ makeServiceModelMenu[ obj, root, model, service ] + catchAlways @ makeServiceModelMenu[ Dynamic @ display, obj, root, model, service ] ], SynchronousInitialization -> False ]; @@ -993,14 +996,56 @@ dynamicModelMenu // endDefinition; (*makeServiceModelMenu*) makeServiceModelMenu // beginDefinition; -makeServiceModelMenu[ obj_, root_, currentModel_, service_String ] := - makeServiceModelMenu[ obj, root, currentModel, service, getServiceModelList @ service ]; +makeServiceModelMenu[ display_, obj_, root_, currentModel_, service_String ] := + makeServiceModelMenu[ + display, + obj, + root, + currentModel, + service, + Block[ { $allowConnectionDialog = False }, getServiceModelList @ service ] + ]; + +makeServiceModelMenu[ Dynamic[ display_ ], obj_, root_, currentModel_, service_String, models_List ] := + display = MakeMenu[ + Join[ { service }, groupMenuModels[ obj, root, currentModel, models ] ], + GrayLevel[ 0.85 ], + 280 + ]; -makeServiceModelMenu[ obj_, root_, currentModel_, service_String, models_List ] := - MakeMenu[ Join[ { service }, groupMenuModels[ obj, root, currentModel, models ] ], GrayLevel[ 0.85 ], 280 ]; +makeServiceModelMenu[ Dynamic[ display_ ], obj_, root_, currentModel_, service_String, Missing[ "NotConnected" ] ] := + display = MakeMenu[ + { + { service }, + { + Spacer[ 0 ], + "Connect for model list", + Hold[ + display = simpleModelMenuDisplay[ service, ProgressIndicator[ Appearance -> "Percolate" ] ]; + makeServiceModelMenu[ + Dynamic @ display, + obj, + root, + currentModel, + service, + getServiceModelList @ service + ] + ] + } + }, + GrayLevel[ 0.85 ], + 200 + ]; makeServiceModelMenu // endDefinition; +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*simpleModelMenuDisplay*) +simpleModelMenuDisplay // beginDefinition; +simpleModelMenuDisplay[ service_, expr_ ] := MakeMenu[ { { service }, { None, expr, None } }, GrayLevel[ 0.85 ], 200 ]; +simpleModelMenuDisplay // endDefinition; + (* ::**************************************************************************************************************:: *) (* ::Subsubsection::Closed:: *) (*groupMenuModels*) @@ -1057,7 +1102,7 @@ modelMenuItem[ ] := { alignedMenuIcon[ modelSelectionCheckmark[ currentModel, name ], icon ], displayName, - Hold[ removeChatMenus @ root; setModel[ obj, model ] ] + Hold[ removeChatMenus @ EvaluationCell[ ]; setModel[ obj, model ] ] }; modelMenuItem // endDefinition; From 10ee2d7c99a93b90e627ce89f5d0c35e9f2aa522 Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Fri, 15 Dec 2023 13:46:46 -0500 Subject: [PATCH 46/50] Bugfix: avoid line breaking in toolbar menu --- Source/Chatbook/UI.wl | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/Source/Chatbook/UI.wl b/Source/Chatbook/UI.wl index 073d38b2..933f77dd 100644 --- a/Source/Chatbook/UI.wl +++ b/Source/Chatbook/UI.wl @@ -279,7 +279,7 @@ makeAutomaticResultAnalysisCheckbox[ SetFallthroughError[labeledCheckbox] -labeledCheckbox[value_, label_, enabled_ : Automatic] := +labeledCheckbox[value_, label_, enabled_ : Automatic] := Style[ Row[ { Checkbox[ @@ -297,7 +297,9 @@ labeledCheckbox[value_, label_, enabled_ : Automatic] := Preferences.nb *) CheckboxBoxOptions -> { ImageMargins -> 0 } } - ] + ], + LineBreakWithin -> False +] (*====================================*) From 71b9711ace8aecb66d5ca958b3c9e536af1b1fb2 Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Fri, 15 Dec 2023 15:11:41 -0500 Subject: [PATCH 47/50] Bugfix: clear attached submenus when mousing over a leaf menu item --- Source/Chatbook/Menus.wl | 42 +++++++++++++++++++++++++++++++++++----- 1 file changed, 37 insertions(+), 5 deletions(-) diff --git a/Source/Chatbook/Menus.wl b/Source/Chatbook/Menus.wl index 39ea2b11..4a178c62 100644 --- a/Source/Chatbook/Menus.wl +++ b/Source/Chatbook/Menus.wl @@ -36,6 +36,11 @@ Needs[ "Wolfram`Chatbook`Common`" ]; Needs[ "Wolfram`Chatbook`ErrorUtils`" ]; Needs[ "Wolfram`Chatbook`FrontEnd`" ]; +(* ::**************************************************************************************************************:: *) +(* ::Section::Closed:: *) +(*Configuration*) +$submenuItems = False; + (* ::**************************************************************************************************************:: *) (* ::Section::Closed:: *) (*MakeMenu*) @@ -53,6 +58,10 @@ MakeMenu[ items_List, Automatic, width_ ] := MakeMenu[ items_List, frameColor_, Automatic ] := MakeMenu[ items, frameColor, 200 ]; +MakeMenu[ items_List, frameColor_, width_ ] /; + ! $submenuItems && MemberQ[ items, KeyValuePattern[ "Type" -> "Submenu" ] ] := + Block[ { $submenuItems = True }, MakeMenu[ items, frameColor, width ] ]; + MakeMenu[ items_List, frameColor_, width_ ] := Pane[ RawBoxes @ TemplateBox[ @@ -81,13 +90,16 @@ menuItem[ spec: KeyValuePattern[ "Data" -> content_ ] ] := menuItem[ spec: KeyValuePattern @ { "Type" -> "Submenu", "Data" :> content_ } ] := EventHandler[ + Block[ { $submenuItems = False }, menuItem[ Lookup[ spec, "Icon", Spacer[ 0 ] ], submenuLabel @ Lookup[ spec, "Label", "" ], None + ] ], { - "MouseEntered" :> With[ { root = EvaluationBox[ ] }, AttachSubmenu[ root, content ] ] + "MouseEntered" :> With[ { root = EvaluationBox[ ] }, AttachSubmenu[ root, content ] ], + "MouseDown" :> With[ { root = EvaluationBox[ ] }, AttachSubmenu[ root, content ] ] } ]; @@ -95,13 +107,13 @@ menuItem[ { args__ } ] := menuItem @ args; menuItem[ Delimiter ] := - RawBoxes @ TemplateBox[ { }, "ChatMenuItemDelimiter" ]; + addSubmenuHandler @ RawBoxes @ TemplateBox[ { }, "ChatMenuItemDelimiter" ]; menuItem[ label_ :> action_ ] := menuItem[ Graphics[ { }, ImageSize -> 0 ], label, Hold @ action ]; menuItem[ section_ ] := - RawBoxes @ TemplateBox[ { ToBoxes @ section }, "ChatMenuSection" ]; + addSubmenuHandler @ RawBoxes @ TemplateBox[ { ToBoxes @ section }, "ChatMenuSection" ]; menuItem[ name_String, label_, code_ ] := With[ { icon = chatbookIcon @ name }, @@ -125,16 +137,36 @@ menuItem[ icon_, label_, action_String ] := ]; menuItem[ None, content_, None ] := - content; + addSubmenuHandler @ content; menuItem[ icon_, label_, None ] := menuItem[ icon, label, Hold @ Null ]; menuItem[ icon_, label_, code_ ] := - RawBoxes @ TemplateBox[ { ToBoxes @ icon, ToBoxes @ label, code }, "ChatMenuItem" ]; + addSubmenuHandler @ RawBoxes @ TemplateBox[ { ToBoxes @ icon, ToBoxes @ label, code }, "ChatMenuItem" ]; menuItem // endDefinition; +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*addSubmenuHandler*) +addSubmenuHandler // beginDefinition; + +addSubmenuHandler[ expr_ ] /; $submenuItems := EventHandler[ + expr, + { + "MouseEntered" :> NotebookDelete @ Cells[ + EvaluationCell[ ], + AttachedCell -> True, + CellStyle -> "AttachedChatMenu" + ] + } +]; + +addSubmenuHandler[ expr_ ] := expr; + +addSubmenuHandler // endDefinition; + (* ::**************************************************************************************************************:: *) (* ::Subsection::Closed:: *) (*submenuLabel*) From e422b4da1afb57847823d224f9a995a1e479e5a2 Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Fri, 15 Dec 2023 15:14:50 -0500 Subject: [PATCH 48/50] Bugfix: limit the vertical size of menus and add a scrollbar if necessary --- Source/Chatbook/Menus.wl | 10 ++++++---- 1 file changed, 6 insertions(+), 4 deletions(-) diff --git a/Source/Chatbook/Menus.wl b/Source/Chatbook/Menus.wl index 4a178c62..e19869b9 100644 --- a/Source/Chatbook/Menus.wl +++ b/Source/Chatbook/Menus.wl @@ -63,10 +63,14 @@ MakeMenu[ items_List, frameColor_, width_ ] /; Block[ { $submenuItems = True }, MakeMenu[ items, frameColor, width ] ]; MakeMenu[ items_List, frameColor_, width_ ] := - Pane[ RawBoxes @ TemplateBox[ { - ToBoxes @ Column[ menuItem /@ items, ItemSize -> Automatic, Spacings -> 0, Alignment -> Left ], + ToBoxes @ Pane[ + Column[ menuItem /@ items, ItemSize -> Automatic, Spacings -> 0, Alignment -> Left ], + AppearanceElements -> None, + ImageSize -> { width, UpTo[ 450 ] }, + Scrollbars -> { False, Automatic } + ], Background -> GrayLevel[ 0.98 ], FrameMargins -> 3, FrameStyle -> Directive[ AbsoluteThickness[ 1 ], frameColor ], @@ -74,8 +78,6 @@ MakeMenu[ items_List, frameColor_, width_ ] := RoundingRadius -> 3 }, "Highlighted" - ], - ImageSize -> { width, Automatic } ]; MakeMenu // endDefinition; From cfdaf386de55d485c6240b1078c1772dc4715173 Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Fri, 15 Dec 2023 15:15:57 -0500 Subject: [PATCH 49/50] Improve vertical offsets to avoid menu going outside of content area --- Source/Chatbook/Menus.wl | 51 ++++++++++++++++++++++++++-------------- 1 file changed, 34 insertions(+), 17 deletions(-) diff --git a/Source/Chatbook/Menus.wl b/Source/Chatbook/Menus.wl index e19869b9..5676a4b9 100644 --- a/Source/Chatbook/Menus.wl +++ b/Source/Chatbook/Menus.wl @@ -63,21 +63,21 @@ MakeMenu[ items_List, frameColor_, width_ ] /; Block[ { $submenuItems = True }, MakeMenu[ items, frameColor, width ] ]; MakeMenu[ items_List, frameColor_, width_ ] := - RawBoxes @ TemplateBox[ - { + RawBoxes @ TemplateBox[ + { ToBoxes @ Pane[ Column[ menuItem /@ items, ItemSize -> Automatic, Spacings -> 0, Alignment -> Left ], AppearanceElements -> None, ImageSize -> { width, UpTo[ 450 ] }, Scrollbars -> { False, Automatic } ], - Background -> GrayLevel[ 0.98 ], - FrameMargins -> 3, - FrameStyle -> Directive[ AbsoluteThickness[ 1 ], frameColor ], - ImageMargins -> 0, - RoundingRadius -> 3 - }, - "Highlighted" + Background -> GrayLevel[ 0.98 ], + FrameMargins -> 3, + FrameStyle -> Directive[ AbsoluteThickness[ 1 ], frameColor ], + ImageMargins -> 0, + RoundingRadius -> 3 + }, + "Highlighted" ]; MakeMenu // endDefinition; @@ -93,10 +93,10 @@ menuItem[ spec: KeyValuePattern[ "Data" -> content_ ] ] := menuItem[ spec: KeyValuePattern @ { "Type" -> "Submenu", "Data" :> content_ } ] := EventHandler[ Block[ { $submenuItems = False }, - menuItem[ - Lookup[ spec, "Icon", Spacer[ 0 ] ], - submenuLabel @ Lookup[ spec, "Label", "" ], - None + menuItem[ + Lookup[ spec, "Icon", Spacer[ 0 ] ], + submenuLabel @ Lookup[ spec, "Label", "" ], + None ] ], { @@ -250,17 +250,34 @@ menuMagnification // endDefinition; (*determineAttachmentPosition*) determineAttachmentPosition // beginDefinition; -determineAttachmentPosition[ info_Association ] := - Lookup[ info, "Position", determineAttachmentPosition @ MousePosition[ "WindowScaled" ] ]; +determineAttachmentPosition[ KeyValuePattern[ "Position" -> { { pH_, pV_ }, { oH_, oV_ } } ] ] := + { { pH, pV }, { oH, chooseVerticalOffset @ MousePosition[ "WindowScaled" ] } }; + +determineAttachmentPosition[ _Association ] := + determineAttachmentPosition @ MousePosition[ "WindowScaled" ]; determineAttachmentPosition[ pos_List ] := determineAttachmentPosition[ pos, quadrant @ pos ]; -determineAttachmentPosition[ _, { h_, v_ } ] := - { { Replace[ h, { Left -> Right, Right -> Left } ], v }, { h, Center } }; +determineAttachmentPosition[ { x_, y_ }, { h_, v_ } ] := { + { Replace[ h, { Left -> Right, Right -> Left } ], v }, + { h, chooseVerticalOffset @ { x, y } } +}; + +determineAttachmentPosition[ None ] := + { { Right, Top }, { Left, Top } }; determineAttachmentPosition // endDefinition; +(* ::**************************************************************************************************************:: *) +(* ::Subsubsection::Closed:: *) +(*chooseVerticalOffset*) +chooseVerticalOffset // beginDefinition; +chooseVerticalOffset[ { x_, y_ } ] /; y < 0.33 := Top; +chooseVerticalOffset[ { x_, y_ } ] /; y > 0.67 := Bottom; +chooseVerticalOffset[ { x_, y_ } ] := Center; +chooseVerticalOffset // endDefinition; + (* ::**************************************************************************************************************:: *) (* ::Subsubsection::Closed:: *) (*quadrant*) From 6979069247eb7208ee627215282f8b36e3ff06ba Mon Sep 17 00:00:00 2001 From: Rick Hennigan Date: Fri, 15 Dec 2023 15:16:28 -0500 Subject: [PATCH 50/50] Determine vertical attachment direction for dingbat menus based on window position --- Source/Chatbook/UI.wl | 18 +++++++++--------- 1 file changed, 9 insertions(+), 9 deletions(-) diff --git a/Source/Chatbook/UI.wl b/Source/Chatbook/UI.wl index 933f77dd..5a67436a 100644 --- a/Source/Chatbook/UI.wl +++ b/Source/Chatbook/UI.wl @@ -444,7 +444,7 @@ MakeChatInputActiveCellDingbat[cell_CellObject] := Module[{ ImageMargins -> 0, ContentPadding -> False ], - ( + With[ { pos = Replace[ MousePosition[ "WindowScaled" ], { { _, y_ } :> y, _ :> 0 } ] }, attachMenuCell[ EvaluationCell[], makeChatActionMenu[ @@ -452,12 +452,12 @@ MakeChatInputActiveCellDingbat[cell_CellObject] := Module[{ parentCell[EvaluationCell[]], EvaluationCell[] ], - {Left, Bottom}, + {Left, If[ pos < 0.5, Bottom, Top ]}, Offset[{0, 0}, {Left, Top}], - {Left, Top}, + {Left, If[ pos < 0.5, Top, Bottom ]}, RemovalConditions -> {"EvaluatorQuit", "MouseClickOutside"} - ]; - ), + ] + ], Appearance -> $suppressButtonAppearance, ImageMargins -> 0, FrameMargins -> 0, @@ -536,7 +536,7 @@ MakeChatDelimiterCellDingbat[cell_CellObject] := Module[{ ImageMargins -> 0, ContentPadding -> False ], - ( + With[ { pos = Replace[ MousePosition[ "WindowScaled" ], { { _, y_ } :> y, _ :> 0 } ] }, attachMenuCell[ EvaluationCell[], makeChatActionMenu[ @@ -544,12 +544,12 @@ MakeChatDelimiterCellDingbat[cell_CellObject] := Module[{ parentCell[EvaluationCell[]], EvaluationCell[] ], - {Left, Bottom}, + {Left, If[ pos < 0.5, Bottom, Top ]}, Offset[{0, 0}, {Left, Top}], - {Left, Top}, + {Left, If[ pos < 0.5, Top, Bottom ]}, RemovalConditions -> {"EvaluatorQuit", "MouseClickOutside"} ]; - ), + ], Appearance -> $suppressButtonAppearance, ImageMargins -> 0, FrameMargins -> 0,