Skip to content

Commit b7d499e

Browse files
committed
Merge branch 'master' of ssh://stash.wolfram.com:7999/se/wolframlanguageforjupyter
2 parents 2139610 + 486789f commit b7d499e

File tree

4 files changed

+368
-201
lines changed

4 files changed

+368
-201
lines changed

README README.md

File renamed without changes.

WolframLanguageForJupyter/Resources/kernel.wl

+158-132
Original file line numberDiff line numberDiff line change
@@ -72,11 +72,17 @@ SetAttributes[jupEval, HoldAll];
7272

7373
sendFrame[socket_, frame_Association] := Module[{},
7474

75+
ZeroMQLink`ZMQSocketWriteMessage[
76+
socket,
77+
frame["ident"],
78+
"Multipart" -> True
79+
];
80+
7581
ZeroMQLink`ZMQSocketWriteMessage[
7682
socket,
7783
StringToByteArray[#1],
7884
"Multipart" -> True
79-
]& /@ Lookup[frame, {"uuid", "idsmsg", "signature", "header", "pheader", "metadata"}];
85+
]& /@ Lookup[frame, {"idsmsg", "signature", "header", "pheader", "metadata"}];
8086

8187
ZeroMQLink`ZMQSocketWriteMessage[
8288
socket,
@@ -141,12 +147,12 @@ getFrameAssoc[frame_Association, replyType_String, replyContent_String, branchOf
141147
header = frame["header"];
142148
content = frame["content"];
143149

144-
AssociateTo[res, {"header" -> Association[ImportString[header, "JSON"]], "content" -> Association[ImportString[content, "JSON"]]}];
150+
AssociateTo[res, {"header" -> Association[ImportByteArray[StringToByteArray[header], "JSON"]], "content" -> Association[ImportByteArray[StringToByteArray[content], "JSON"]]}];
145151
AssociateTo[
146152
res,
147153
"replyMsg" ->
148154
Association[
149-
"uuid" -> res["header"]["session"],
155+
"ident" -> If[KeyExistsQ[frame, "ident"], frame["ident"], ByteArray[{0, 0, 0, 0, 0}]],
150156
"idsmsg" -> "<IDS|MSG>",
151157
"header" -> ExportString[Append[res["header"], {"date" -> DateString["ISODateTime"], "msg_type" -> replyType, "msg_id" -> StringInsert[StringReplace[CreateUUID[], "-" -> ""], "-", 9]}], "JSON", "Compact" -> True],
152158
"pheader" -> If[branchOff, "{}", header],
@@ -175,17 +181,17 @@ getFrameAssoc[frame_Association, replyType_String, replyContent_String, branchOf
175181
Return[res];
176182
];
177183

178-
getFrameAssoc[baFrame_ByteArray, replyType_String, replyContent_String, branchOff:(True|False)] := Module[{frameStr, res = Association[], header, pheader, metadata, content},
184+
getFrameAssoc[baFrame_ByteArray, replyType_String, replyContent_String, branchOff:(True|False)] := Module[{frameStr, res = Association[], identLen, header, pheader, metadata, content},
179185
frameStr = Quiet[ByteArrayToString[baFrame]];
180186

181-
{header, pheader, metadata, content} = First[StringCases[frameStr,
182-
"<IDS|MSG>" ~~ ___ ~~ "{" ~~ json1___ ~~ "}" ~~ "{" ~~ json2___ ~~ "}" ~~ "{" ~~ json3___ ~~ "}" ~~ "{" ~~ json4___ ~~ "}" ~~ EndOfString :>
183-
(StringJoin["{",#1,"}"] &) /@ {json1,json2,json3,json4}
187+
{identLen, header, pheader, metadata, content} = First[StringCases[frameStr,
188+
ident1___ ~~ "<IDS|MSG>" ~~ ___ ~~ "{" ~~ json1___ ~~ "}" ~~ "{" ~~ json2___ ~~ "}" ~~ "{" ~~ json3___ ~~ "}" ~~ "{" ~~ json4___ ~~ "}" ~~ EndOfString :>
189+
Prepend[(StringJoin["{",#1,"}"] &) /@ {json1,json2,json3,json4}, StringLength[ident1]]
184190
]];
185191

186192
Return[
187193
getFrameAssoc[
188-
Association["header" -> header, "content" -> content],
194+
Association["ident" -> baFrame[[;;identLen]], "header" -> header, "content" -> content],
189195
replyType,
190196
replyContent,
191197
branchOff
@@ -249,142 +255,162 @@ ioPubReplyFrame = Association[];
249255

250256
doShutdown = False;
251257

252-
While[
253-
True,
254-
Switch[
255-
First[SocketWaitNext[{shellSocket}]],
256-
shellSocket,
257-
srm = SocketReadMessage[shellSocket, "Multipart" -> True];
258-
frameAssoc = getFrameAssoc[srm, "", "{}", False];
259-
Switch[
260-
frameAssoc["header"]["msg_type"],
261-
"kernel_info_request",
262-
replyMsgType = "kernel_info_reply";
263-
replyContent = "{\"protocol_version\":\"5.3.0\",\"implementation\":\"WL\"}";,
264-
"is_complete_request",
265-
(* Add syntax-Q checking *)
266-
replyMsgType = "is_complete_reply";
267-
replyContent = "{\"status\":\"unknown\"}";,
268-
"execute_request",
269-
270-
replyMsgType = "execute_reply";
271-
replyContent = ExportString[Association["status" -> "ok", "execution_count" -> executionCount, "user_expressions" -> {}], "JSON", "Compact" -> True];
272-
273-
$jupResEval = ToExpression[frameAssoc["content"]["code"], InputForm, Uninteract];
274-
$res = $jupResEval["res"];
275-
$msgs = $jupResEval["msgs"];
276-
If[FailureQ[$jupResEval],
277-
$res=$Failed;
278-
$msgs=jupEval[ToExpression[frameAssoc["content"]["code"], InputForm]]["msgs"];
279-
];
258+
jupyterEvaluationLoop[] :=
259+
Module[
260+
{
261+
srm,
262+
frameAssoc,
263+
replyMsgType,
264+
replyContent,
265+
$jupResEval,
266+
$res,
267+
$msgs,
268+
ioPubReplyContent,
269+
statReplyFrame,
270+
shellReplyFrame
271+
},
272+
273+
While[
274+
True,
275+
Switch[
276+
First[SocketWaitNext[{shellSocket}]],
277+
shellSocket,
278+
srm = SocketReadMessage[shellSocket, "Multipart" -> True];
279+
frameAssoc = getFrameAssoc[srm, "", "{}", False];
280+
Switch[
281+
frameAssoc["header"]["msg_type"],
282+
"kernel_info_request",
283+
replyMsgType = "kernel_info_reply";
284+
replyContent = "{\"protocol_version\":\"5.3.0\",\"implementation\":\"WL\"}";,
285+
"is_complete_request",
286+
(* Add syntax-Q checking *)
287+
replyMsgType = "is_complete_reply";
288+
replyContent = "{\"status\":\"unknown\"}";,
289+
"execute_request",
290+
291+
replyMsgType = "execute_reply";
292+
replyContent = ExportString[Association["status" -> "ok", "execution_count" -> executionCount, "user_expressions" -> {}], "JSON", "Compact" -> True];
293+
294+
$jupResEval = ToExpression[frameAssoc["content"]["code"], InputForm, Uninteract];
295+
$res = $jupResEval["res"];
296+
$msgs = $jupResEval["msgs"];
297+
If[FailureQ[$jupResEval],
298+
$res=$Failed;
299+
$msgs=jupEval[ToExpression[frameAssoc["content"]["code"], InputForm]]["msgs"];
300+
];
280301

281-
If[TrueQ[InteractQ[ToExpression[frameAssoc["content"]["code"], InputForm, Hold]]] && $CloudConnected,
282-
ioPubReplyContent = ExportString[
283-
Association[
284-
"execution_count" -> executionCount,
285-
"data" -> {"text/html" -> StringJoin[
286-
"<div><img alt=\"\" src=\"data:image/png;base64,",
287-
BaseEncode[ExportByteArray[Rasterize[Style[$msgs, Darker[Red]]], "PNG"]],
302+
If[TrueQ[InteractQ[ToExpression[frameAssoc["content"]["code"], InputForm, Hold]]] && $CloudConnected,
303+
ioPubReplyContent = ExportString[
304+
Association[
305+
"execution_count" -> executionCount,
306+
"data" -> {"text/html" -> StringJoin[
307+
"<div><img alt=\"\" src=\"data:image/png;base64,",
308+
BaseEncode[ExportByteArray[Rasterize[Style[$msgs, Darker[Red]]], "PNG"]],
309+
"\">",
310+
EmbedCode[CloudDeploy[$res], "HTML"][[1]]["CodeSection"]["Content"],
311+
"</div>"
312+
]
313+
},
314+
"metadata" -> {"text/html" -> {}}
315+
],
316+
"JSON",
317+
"Compact" -> True
318+
];
319+
,
320+
If[doText[$res],
321+
ioPubReplyContent = ExportString[
322+
Association[
323+
"execution_count" -> executionCount,
324+
"data" -> {"text/html" -> StringJoin[
325+
"<div>",
326+
If[StringLength[$msgs] == 0,
327+
{},
328+
{
329+
"<pre style=\"",
330+
StringJoin[{"&#",ToString[#1], ";"} & /@ ToCharacterCode["color:red; font-family: \"Courier New\",Courier,monospace;"]],
288331
"\">",
289-
EmbedCode[CloudDeploy[$res], "HTML"][[1]]["CodeSection"]["Content"],
290-
"</div>"
291-
]
292-
},
293-
"metadata" -> {"text/html" -> {}}
294-
],
295-
"JSON",
296-
"Compact" -> True
297-
];
298-
,
299-
If[doText[$res],
300-
ioPubReplyContent = ExportString[
301-
Association[
302-
"execution_count" -> executionCount,
303-
"data" -> {"text/html" -> StringJoin[
304-
"<div>",
305-
If[StringLength[$msgs] == 0,
306-
{},
307-
{
308-
"<pre style=\"",
309-
StringJoin[{"&#",ToString[#1], ";"} & /@ ToCharacterCode["color:red; font-family: \"Courier New\",Courier,monospace;"]],
310-
"\">",
311-
StringJoin[{"&#", ToString[#1], ";"} & /@ ToCharacterCode[$msgs]],
312-
"</pre>"
313-
}
314-
],
315-
"<pre style=\"",
316-
StringJoin[{"&#",ToString[#1], ";"} & /@ ToCharacterCode["font-family: \"Courier New\",Courier,monospace;"]],
317-
"\">",
318-
StringJoin[{"&#", ToString[#1], ";"} & /@ ToCharacterCode[ToString[$res]]],
319-
"</pre></div>"
320-
]
321-
},
322-
"metadata" -> {"text/html" -> {}}
323-
],
324-
"JSON",
325-
"Compact" -> True
326-
];,
327-
ioPubReplyContent = ExportString[
328-
Association[
329-
"execution_count" -> executionCount,
330-
"data" -> {"text/html" -> StringJoin[
331-
"<div>",
332-
Sequence @@ If[StringLength[$msgs] == 0,
333-
{},
334-
{
332+
StringJoin[{"&#", ToString[#1], ";"} & /@ ToCharacterCode[$msgs]],
333+
"</pre>"
334+
}
335+
],
335336
"<pre style=\"",
336-
StringJoin[{"&#",ToString[#1], ";"} & /@ ToCharacterCode["color:red; font-family: \"Courier New\",Courier,monospace;"]],
337+
StringJoin[{"&#",ToString[#1], ";"} & /@ ToCharacterCode["font-family: \"Courier New\",Courier,monospace;"]],
337338
"\">",
338-
StringJoin[{"&#", ToString[#1], ";"} & /@ ToCharacterCode[$msgs]],
339-
"</pre>"
340-
}
341-
],
342-
"<img alt=\"Output\" src=\"data:image/png;base64,",
343-
BaseEncode[
344-
ExportByteArray[
345-
If[Head[$res] === Manipulate, $res, Rasterize[$res]],
346-
"PNG"
339+
StringJoin[{"&#", ToString[#1], ";"} & /@ ToCharacterCode[ToString[$res]]],
340+
"</pre></div>"
341+
]
342+
},
343+
"metadata" -> {"text/html" -> {}}
344+
],
345+
"JSON",
346+
"Compact" -> True
347+
];,
348+
ioPubReplyContent = ExportString[
349+
Association[
350+
"execution_count" -> executionCount,
351+
"data" -> {"text/html" -> StringJoin[
352+
"<div>",
353+
Sequence @@ If[StringLength[$msgs] == 0,
354+
{},
355+
{
356+
"<pre style=\"",
357+
StringJoin[{"&#",ToString[#1], ";"} & /@ ToCharacterCode["color:red; font-family: \"Courier New\",Courier,monospace;"]],
358+
"\">",
359+
StringJoin[{"&#", ToString[#1], ";"} & /@ ToCharacterCode[$msgs]],
360+
"</pre>"
361+
}
362+
],
363+
"<img alt=\"Output\" src=\"data:image/png;base64,",
364+
BaseEncode[
365+
ExportByteArray[
366+
If[Head[$res] === Manipulate, $res, Rasterize[$res]],
367+
"PNG"
368+
]
369+
],
370+
"\"></div>"
347371
]
348-
],
349-
"\"></div>"
350-
]
351-
},
352-
"metadata" -> {"text/html" -> {}}
353-
],
354-
"JSON",
355-
"Compact" -> True
372+
},
373+
"metadata" -> {"text/html" -> {}}
374+
],
375+
"JSON",
376+
"Compact" -> True
377+
];
378+
];
356379
];
380+
381+
ioPubReplyFrame = getFrameAssoc[srm, "execute_result", ioPubReplyContent, False];
382+
383+
executionCount++;,
384+
"shutdown_request",
385+
replyMsgType = "shutdown_reply";
386+
replyContent = "{\"restart\":false}";
387+
doShutdown = True;,
388+
_,
389+
Continue[];
357390
];
358-
];
391+
statReplyFrame = getFrameAssoc[srm, "status", "{\"execution_state\":\"busy\"}", True]["replyMsg"];
392+
sendFrame[ioPubSocket, statReplyFrame];
359393

360-
ioPubReplyFrame = getFrameAssoc[srm, "execute_result", ioPubReplyContent, False];
394+
shellReplyFrame = getFrameAssoc[srm, replyMsgType, replyContent, False];
395+
sendFrame[shellSocket, shellReplyFrame["replyMsg"]];
361396

362-
executionCount++;,
363-
"shutdown_request",
364-
replyMsgType = "shutdown_reply";
365-
replyContent = "{\"restart\":false}";
366-
doShutdown = True;,
367-
_,
368-
Continue[];
369-
];
370-
statReplyFrame = getFrameAssoc[srm, "status", "{\"execution_state\":\"busy\"}", True]["replyMsg"];
371-
sendFrame[ioPubSocket, statReplyFrame];
397+
If[!(ioPubReplyFrame === Association[]),
398+
sendFrame[ioPubSocket, ioPubReplyFrame["replyMsg"]];
399+
ioPubReplyFrame = Association[];
400+
];
372401

373-
shellReplyFrame = getFrameAssoc[srm, replyMsgType, replyContent, False];
374-
sendFrame[shellSocket, shellReplyFrame["replyMsg"]];
402+
sendFrame[ioPubSocket, getFrameAssoc[statReplyFrame, "status", "{\"execution_state\":\"idle\"}", False]["replyMsg"]];
375403

376-
If[!(ioPubReplyFrame === Association[]),
377-
sendFrame[ioPubSocket, ioPubReplyFrame["replyMsg"]];
378-
ioPubReplyFrame = Association[];
404+
If[doShutdown, Quit[];];
405+
,
406+
_,
407+
Continue[];
408+
];
379409
];
410+
];
380411

381-
sendFrame[ioPubSocket, getFrameAssoc[statReplyFrame, "status", "{\"execution_state\":\"idle\"}", False]["replyMsg"]];
412+
End[];
382413

383-
If[doShutdown, Quit[];];
384-
,
385-
_,
386-
Continue[];
387-
];
388-
];
414+
(* This setup does not preclude dynamics or widgets. *)
389415

390-
End[];
416+
WolframLanguageForJupyter`Private`jupyterEvaluationLoop[];

0 commit comments

Comments
 (0)