forked from IHaskell/IHaskell
-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathMain.hs
440 lines (375 loc) · 17.9 KB
/
Main.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
{-# language NoImplicitPrelude, DoAndIfThenElse, OverloadedStrings, ExtendedDefaultRules #-}
{-# LANGUAGE CPP, ScopedTypeVariables #-}
-- | Description : Argument parsing and basic messaging loop, using Haskell
-- Chans to communicate with the ZeroMQ sockets.
module Main (main) where
import IHaskellPrelude
import qualified Data.Text as T
import qualified Data.ByteString.Lazy as LBS
-- Standard library imports.
import Control.Concurrent.Chan
import Control.Arrow (second)
import Data.Aeson hiding (Success)
import System.Process (readProcess, readProcessWithExitCode)
import System.Exit (exitSuccess, ExitCode(ExitSuccess))
import Control.Exception (try, SomeException)
import System.Environment (getArgs)
import System.Environment (setEnv)
import System.Posix.Signals
import qualified Data.Map as Map
import qualified Data.HashMap.Strict as HashMap
import Data.List (break, last)
import Data.Version (showVersion)
-- IHaskell imports.
import IHaskell.Convert (convert)
import IHaskell.Eval.Completion (complete)
import IHaskell.Eval.Inspect (inspect)
import IHaskell.Eval.Evaluate
import IHaskell.Display
import IHaskell.Eval.Widgets (widgetHandler)
import IHaskell.Flags
import IHaskell.IPython
import IHaskell.Types
import IHaskell.Publish
import IHaskell.IPython.ZeroMQ
import IHaskell.IPython.Types
import qualified IHaskell.IPython.Message.UUID as UUID
import qualified IHaskell.IPython.Stdin as Stdin
-- Cabal imports.
import Paths_ihaskell(version)
main :: IO ()
main = do
args <- parseFlags <$> getArgs
case args of
Left errorMessage -> hPutStrLn stderr errorMessage
Right xs -> ihaskell xs
ihaskell :: Args -> IO ()
ihaskell (Args (ShowDefault helpStr) args) = showDefault helpStr args
ihaskell (Args ConvertLhs args) = showingHelp ConvertLhs args $ convert args
ihaskell (Args InstallKernelSpec args) = showingHelp InstallKernelSpec args $ do
let kernelSpecOpts = parseKernelArgs args
replaceIPythonKernelspec kernelSpecOpts
ihaskell (Args (Kernel (Just filename)) args) = do
let kernelSpecOpts = parseKernelArgs args
runKernel kernelSpecOpts filename
ihaskell a@(Args (Kernel Nothing) _) = do
hPutStrLn stderr "No kernel profile JSON specified."
hPutStrLn stderr "This may be a bug!"
hPrint stderr a
showDefault :: String -> [Argument] -> IO ()
showDefault helpStr flags =
case find (== Version) flags of
Just _ ->
putStrLn (showVersion version)
Nothing ->
putStrLn helpStr
showingHelp :: IHaskellMode -> [Argument] -> IO () -> IO ()
showingHelp mode flags act =
case find (== Help) flags of
Just _ ->
putStrLn $ help mode
Nothing ->
act
-- | Parse initialization information from the flags.
parseKernelArgs :: [Argument] -> KernelSpecOptions
parseKernelArgs = foldl' addFlag defaultKernelSpecOptions
where
addFlag kernelSpecOpts (ConfFile filename) =
kernelSpecOpts { kernelSpecConfFile = return (Just filename) }
addFlag kernelSpecOpts KernelDebug =
kernelSpecOpts { kernelSpecDebug = True }
addFlag kernelSpecOpts (GhcLibDir libdir) =
kernelSpecOpts { kernelSpecGhcLibdir = libdir }
addFlag kernelSpecOpts (RTSFlags rts) =
kernelSpecOpts { kernelSpecRTSOptions = rts }
addFlag kernelSpecOpts (KernelspecInstallPrefix prefix) =
kernelSpecOpts { kernelSpecInstallPrefix = Just prefix }
addFlag kernelSpecOpts KernelspecUseStack =
kernelSpecOpts { kernelSpecUseStack = True }
addFlag _kernelSpecOpts flag = error $ "Unknown flag" ++ show flag
-- | Run the IHaskell language kernel.
runKernel :: KernelSpecOptions -- ^ Various options from when the kernel was installed.
-> String -- ^ File with kernel profile JSON (ports, etc).
-> IO ()
runKernel kOpts profileSrc = do
let debug = kernelSpecDebug kOpts
libdir = kernelSpecGhcLibdir kOpts
useStack = kernelSpecUseStack kOpts
-- Parse the profile file.
let profileErr = error $ "ihaskell: "++profileSrc++": Failed to parse profile file"
profile <- liftM (fromMaybe profileErr . decode) $ LBS.readFile profileSrc
-- Necessary for `getLine` and their ilk to work.
dir <- getIHaskellDir
Stdin.recordKernelProfile dir profile
when useStack $ do
-- Detect if we have stack
runResult <- try $ readProcessWithExitCode "stack" [] ""
let stack =
case runResult :: Either SomeException (ExitCode, String, String) of
Left _ -> False
Right (exitCode, stackStdout, _) -> exitCode == ExitSuccess && "The Haskell Tool Stack" `isInfixOf` stackStdout
-- If we're in a stack directory, use `stack` to set the environment
-- We can't do this with base <= 4.6 because setEnv doesn't exist.
when stack $ do
stackEnv <- lines <$> readProcess "stack" ["exec", "env"] ""
forM_ stackEnv $ \line ->
let (var, val) = break (== '=') line
in case tailMay val of
Nothing -> return ()
Just val' -> setEnv var val'
-- Serve on all sockets and ports defined in the profile.
interface <- serveProfile profile debug
-- Create initial state in the directory the kernel *should* be in.
state <- initialKernelState
modifyMVar_ state $ \kernelState -> return $
kernelState { kernelDebug = debug }
-- Receive and reply to all messages on the shell socket.
interpret libdir True True $ \hasSupportLibraries -> do
-- Ignore Ctrl-C the first time. This has to go inside the `interpret`, because GHC API resets the
-- signal handlers for some reason (completely unknown to me).
_ <- liftIO ignoreCtrlC
liftIO $ modifyMVar_ state $ \kernelState -> return $
kernelState { supportLibrariesAvailable = hasSupportLibraries }
-- Initialize the context by evaluating everything we got from the command line flags.
let noPublish _ _ = return ()
noWidget s _ = return s
evaluator line = void $ do
-- Create a new state each time.
stateVar <- liftIO initialKernelState
st <- liftIO $ takeMVar stateVar
evaluate st line noPublish noWidget
confFile <- liftIO $ kernelSpecConfFile kOpts
case confFile of
Just filename -> liftIO (readFile filename) >>= evaluator
Nothing -> return ()
forever $ do
-- Read the request from the request channel.
request <- liftIO $ readChan $ shellRequestChannel interface
-- Create a header for the reply.
replyHeader <- createReplyHeader (header request)
-- Notify the frontend that the kernel is busy computing. All the headers are copies of the reply
-- header with a different message type, because this preserves the session ID, parent header, and
-- other important information.
busyHeader <- liftIO $ dupHeader replyHeader StatusMessage
liftIO $ writeChan (iopubChannel interface) $ PublishStatus busyHeader Busy
-- We handle comm messages and normal ones separately. The normal ones are a standard
-- request/response style, while comms can be anything, and don't necessarily require a response.
if isCommMessage request
then do
oldState <- liftIO $ takeMVar state
let replier = writeChan (iopubChannel interface)
widgetMessageHandler = widgetHandler replier replyHeader
tempState <- handleComm replier oldState request replyHeader
newState <- flushWidgetMessages tempState [] widgetMessageHandler
liftIO $ putMVar state newState
liftIO $ writeChan (shellReplyChannel interface) SendNothing
else do
-- Create the reply, possibly modifying kernel state.
oldState <- liftIO $ takeMVar state
(newState, reply) <- replyTo interface request replyHeader oldState
liftIO $ putMVar state newState
-- Write the reply to the reply channel.
liftIO $ writeChan (shellReplyChannel interface) reply
-- Notify the frontend that we're done computing.
idleHeader <- liftIO $ dupHeader replyHeader StatusMessage
liftIO $ writeChan (iopubChannel interface) $ PublishStatus idleHeader Idle
where
ignoreCtrlC =
installHandler keyboardSignal (CatchOnce $ putStrLn "Press Ctrl-C again to quit kernel.")
Nothing
isCommMessage req = mhMsgType (header req) `elem` [CommDataMessage, CommCloseMessage]
-- Initial kernel state.
initialKernelState :: IO (MVar KernelState)
initialKernelState = newMVar defaultKernelState
-- | Create a new message header, given a parent message header.
createReplyHeader :: MessageHeader -> Interpreter MessageHeader
createReplyHeader parent = do
-- Generate a new message UUID.
newMessageId <- liftIO UUID.random
let repType = fromMaybe err (replyType $ mhMsgType parent)
err = error $ "No reply for message " ++ show (mhMsgType parent)
return $ MessageHeader (mhIdentifiers parent) (Just parent) mempty
newMessageId (mhSessionId parent) (mhUsername parent) repType []
-- | Compute a reply to a message.
replyTo :: ZeroMQInterface -> Message -> MessageHeader -> KernelState -> Interpreter (KernelState, Message)
-- Reply to kernel info requests with a kernel info reply. No computation needs to be done, as a
-- kernel info reply is a static object (all info is hard coded into the representation of that
-- message type).
replyTo interface KernelInfoRequest{} replyHeader state = do
let send msg = liftIO $ writeChan (iopubChannel interface) msg
-- Notify the frontend that the Kernel is idle
idleHeader <- liftIO $ dupHeader replyHeader StatusMessage
send $ PublishStatus idleHeader Idle
return
(state, KernelInfoReply
{ header = replyHeader
, protocolVersion = "5.0"
, banner = "IHaskell " ++ (showVersion version) ++ " GHC " ++ VERSION_ghc
, implementation = "IHaskell"
, implementationVersion = showVersion version
, languageInfo = LanguageInfo
{ languageName = "haskell"
, languageVersion = VERSION_ghc
, languageFileExtension = ".hs"
, languageCodeMirrorMode = "ihaskell"
, languagePygmentsLexer = "Haskell"
, languageMimeType = "text/x-haskell" -- https://jupyter-client.readthedocs.io/en/stable/wrapperkernels.html#MyKernel.language_info
}
, status = Ok
})
replyTo _ CommInfoRequest{} replyHeader state =
let comms = Map.mapKeys (UUID.uuidToString) (openComms state) in
return
(state, CommInfoReply
{ header = replyHeader
, commInfo = Map.map (\(Widget w) -> targetName w) comms
})
-- Reply to a shutdown request by exiting the main thread. Before shutdown, reply to the request to
-- let the frontend know shutdown is happening.
replyTo interface ShutdownRequest { restartPending = pending } replyHeader _ = liftIO $ do
writeChan (shellReplyChannel interface) $ ShutdownReply replyHeader pending
exitSuccess
-- Reply to an execution request. The reply itself does not require computation, but this causes
-- messages to be sent to the IOPub socket with the output of the code in the execution request.
replyTo interface req@ExecuteRequest { getCode = code } replyHeader state = do
-- Convenience function to send a message to the IOPub socket.
let send msg = liftIO $ writeChan (iopubChannel interface) msg
-- Log things so that we can use stdin.
dir <- liftIO getIHaskellDir
liftIO $ Stdin.recordParentHeader dir $ header req
-- Construct a function for publishing output as this is going. This function accepts a boolean
-- indicating whether this is the final output and the thing to display. Store the final outputs in
-- a list so that when we receive an updated non-final output, we can clear the entire output and
-- re-display with the updated output.
displayed <- liftIO $ newMVar []
updateNeeded <- liftIO $ newMVar False
pOut <- liftIO $ newMVar []
let execCount = getExecutionCounter state
-- Let all frontends know the execution count and code that's about to run
inputHeader <- liftIO $ dupHeader replyHeader ExecuteInputMessage
send $ PublishInput inputHeader (T.unpack code) execCount
-- Run code and publish to the frontend as we go.
let widgetMessageHandler = widgetHandler send replyHeader
publish = publishResult send replyHeader displayed updateNeeded pOut (usePager state)
updatedState <- evaluate state (T.unpack code) publish widgetMessageHandler
-- Take pager output if we're using the pager.
pager <- if usePager state
then liftIO $ readMVar pOut
else return []
return
(updatedState, ExecuteReply
{ header = replyHeader
, pagerOutput = pager
, executionCounter = execCount
, status = Ok
})
-- Check for a trailing empty line. If it doesn't exist, we assume the code is incomplete,
-- otherwise we assume the code is complete. Todo: Implement a mechanism that only requests
-- a trailing empty line, when multiline code is entered.
replyTo _ req@IsCompleteRequest{} replyHeader state = do
isComplete <- isInputComplete
let reply = IsCompleteReply { header = replyHeader, reviewResult = isComplete }
return (state, reply)
where
isInputComplete = do
let code = lines $ inputToReview req
if nub (last code) == " "
then return CodeComplete
else return $ CodeIncomplete $ indent 4
indent n = take n $ repeat ' '
replyTo _ req@CompleteRequest{} replyHeader state = do
let code = getCode req
pos = getCursorPos req
(matchedText, completions) <- complete (T.unpack code) pos
let start = pos - length matchedText
end = pos
reply = CompleteReply replyHeader (map T.pack completions) start end (Metadata HashMap.empty) True
return (state, reply)
replyTo _ req@InspectRequest{} replyHeader state = do
result <- inspect (T.unpack $ inspectCode req) (inspectCursorPos req)
let reply =
case result of
Just (Display datas) -> InspectReply
{ header = replyHeader
, inspectStatus = True
, inspectData = datas
}
_ -> InspectReply { header = replyHeader, inspectStatus = False, inspectData = [] }
return (state, reply)
-- TODO: Implement history_reply.
replyTo _ HistoryRequest{} replyHeader state = do
let reply = HistoryReply
{ header = replyHeader
-- FIXME
, historyReply = []
}
return (state, reply)
-- Accomodating the workaround for retrieving list of open comms from the kernel
--
-- The main idea is that the frontend opens a comm at kernel startup, whose target is a widget that
-- sends back the list of live comms and commits suicide.
--
-- The message needs to be written to the iopub channel, and not returned from here. If returned,
-- the same message also gets written to the shell channel, which causes issues due to two messages
-- having the same identifiers in their headers.
--
-- Sending the message only on the shell_reply channel doesn't work, so we send it as a comm message
-- on the iopub channel and return the SendNothing message.
replyTo interface ocomm@CommOpen{} replyHeader state = do
let send = liftIO . writeChan (iopubChannel interface)
incomingUuid = commUuid ocomm
target = commTargetName ocomm
targetMatches = target == "ipython.widget"
valueMatches = commData ocomm == object ["widget_class" .= ("ipywidgets.CommInfo" :: Text)]
commMap = openComms state
uuidTargetPairs = map (second targetName) $ Map.toList commMap
pairProcessor (x, y) = T.pack (UUID.uuidToString x) .= object ["target_name" .= T.pack y]
currentComms = object $ map pairProcessor $ (incomingUuid, "comm") : uuidTargetPairs
replyValue = object [ "method" .= ("custom" :: Text)
, "content" .= object ["comms" .= currentComms]
]
msg = CommData replyHeader (commUuid ocomm) replyValue
-- To the iopub channel you go
when (targetMatches && valueMatches) $ send msg
return (state, SendNothing)
-- TODO: What else can be implemented?
replyTo _ message _ state = do
liftIO $ hPutStrLn stderr $ "Unimplemented message: " ++ show message
return (state, SendNothing)
-- | Handle comm messages
handleComm :: (Message -> IO ()) -> KernelState -> Message -> MessageHeader -> Interpreter KernelState
handleComm send kernelState req replyHeader = do
-- MVars to hold intermediate data during publishing
displayed <- liftIO $ newMVar []
updateNeeded <- liftIO $ newMVar False
pOut <- liftIO $ newMVar []
let widgets = openComms kernelState
uuid = commUuid req
dat = commData req
communicate value = do
head <- dupHeader replyHeader CommDataMessage
send $ CommData head uuid value
toUsePager = usePager kernelState
-- Create a publisher according to current state, use that to build
-- a function that executes an IO action and publishes the output to
-- the frontend simultaneously.
let run = capturedIO publish kernelState
publish = publishResult send replyHeader displayed updateNeeded pOut toUsePager
newState <- case Map.lookup uuid widgets of
Nothing -> return kernelState
Just (Widget widget) ->
case mhMsgType $ header req of
CommDataMessage -> do
disp <- run $ comm widget dat communicate
pgrOut <- liftIO $ readMVar pOut
liftIO $ publish (FinalResult disp (if toUsePager then pgrOut else []) []) Success
return kernelState
CommCloseMessage -> do
disp <- run $ close widget dat
pgrOut <- liftIO $ readMVar pOut
liftIO $ publish (FinalResult disp (if toUsePager then pgrOut else []) []) Success
return kernelState { openComms = Map.delete uuid widgets }
_ ->
-- Only sensible thing to do.
return kernelState
return newState