mirror of
https://github.com/IHaskell/IHaskell.git
synced 2025-04-16 11:26:08 +00:00
Start fixing easykernel for ipython4; add example
This commit is contained in:
parent
0bdf5ee0a4
commit
cde0a09574
@ -16,7 +16,7 @@ import Data.Monoid ((<>))
|
||||
import qualified Data.Text as T
|
||||
|
||||
import IHaskell.IPython.Kernel
|
||||
import IHaskell.IPython.EasyKernel (installProfile, easyKernel, KernelConfig(..))
|
||||
import IHaskell.IPython.EasyKernel (installKernelspec, easyKernel, KernelConfig(..))
|
||||
|
||||
import System.Environment (getArgs)
|
||||
import System.FilePath ((</>))
|
||||
@ -106,12 +106,15 @@ expr = do
|
||||
parse :: String -> Either ParseError Razor
|
||||
parse = runParser expr () "(input)"
|
||||
|
||||
-- -------------------- Language operations -------------------- | Completion
|
||||
langCompletion :: T.Text -> T.Text -> Int -> Maybe ([T.Text], T.Text, T.Text)
|
||||
langCompletion _code line col =
|
||||
let (before, _) = T.splitAt col line
|
||||
in fmap (\word -> (map T.pack . matchesFor $ T.unpack word, word, word))
|
||||
(lastMaybe (T.words before))
|
||||
-------------------- Language operations --------------------
|
||||
--
|
||||
-- | Completion
|
||||
langCompletion :: Monad m => T.Text -> Int -> m (T.Text, [T.Text])
|
||||
langCompletion code pos = return $
|
||||
let (before, _) = T.splitAt pos code
|
||||
in case lastMaybe (T.words before) of
|
||||
Nothing -> ("", [])
|
||||
Just word -> (word, map T.pack . matchesFor $ T.unpack word)
|
||||
where
|
||||
lastMaybe :: [a] -> Maybe a
|
||||
lastMaybe [] = Nothing
|
||||
@ -122,8 +125,8 @@ langCompletion _code line col =
|
||||
available = ["sleep", "then", "end", "count"] ++ map show [(-1000 :: Int) .. 1000]
|
||||
|
||||
-- | Documentation lookup
|
||||
langInfo :: T.Text -> Maybe (T.Text, T.Text, T.Text)
|
||||
langInfo obj =
|
||||
langInfo :: Monad m => T.Text -> Int -> m (Maybe [DisplayData])
|
||||
langInfo code pos = return $ toDisplay $
|
||||
if | any (T.isPrefixOf obj) ["sleep", "then", "end"] -> Just (obj, sleepDocs, sleepType)
|
||||
| T.isPrefixOf obj "count" -> Just (obj, countDocs, countType)
|
||||
| obj == "+" -> Just (obj, plusDocs, plusType)
|
||||
@ -133,6 +136,12 @@ langInfo obj =
|
||||
, T.all isDigit y -> Just (obj, floatDocs obj, floatType)
|
||||
| otherwise -> Nothing
|
||||
where
|
||||
(before, _) = T.splitAt pos code
|
||||
obj = last $ T.words before
|
||||
|
||||
toDisplay Nothing = Nothing
|
||||
toDisplay (Just (x, y, z)) = Just [DisplayData PlainText $ T.unlines [x, y, z]]
|
||||
|
||||
sleepDocs = "sleep DURATION then VALUE end: sleep DURATION seconds, then eval VALUE"
|
||||
sleepType = "sleep FLOAT then INT end"
|
||||
plusDocs = "Perform addition"
|
||||
@ -207,9 +216,17 @@ execRazor val Count clear send = do
|
||||
mkConfig :: MVar Integer -- ^ The internal state of the execution
|
||||
-> KernelConfig IO [IntermediateEvalRes] (Either ParseError Integer)
|
||||
mkConfig var = KernelConfig
|
||||
{ languageName = "expanded_huttons_razor"
|
||||
, languageVersion = [0, 1, 0]
|
||||
, profileSource = Just . (</> "calc_profile.tar") <$> Paths.getDataDir
|
||||
{ kernelLanguageInfo = LanguageInfo
|
||||
{ languageName = "expanded_huttons_razor"
|
||||
, languageVersion = "1.0.0"
|
||||
, languageFileExtension = ".txt"
|
||||
, languageCodeMirrorMode = "null"
|
||||
}
|
||||
, writeKernelspec = const $ return $ KernelSpec
|
||||
{ kernelDisplayName = "Hutton's Razor"
|
||||
, kernelLanguage = "hutton"
|
||||
, kernelCommand = ["simple-calc-example", "kernel", "{connection_file}"]
|
||||
}
|
||||
, displayResult = displayRes
|
||||
, displayOutput = displayOut
|
||||
, completion = langCompletion
|
||||
@ -242,11 +259,10 @@ main = do
|
||||
case args of
|
||||
["kernel", profileFile] ->
|
||||
easyKernel profileFile (mkConfig val)
|
||||
["setup"] -> do
|
||||
putStrLn "Installing profile..."
|
||||
installProfile (mkConfig val)
|
||||
["install"] -> do
|
||||
putStrLn "Installing kernelspec..."
|
||||
installKernelspec (mkConfig val) False Nothing
|
||||
_ -> do
|
||||
putStrLn "Usage:"
|
||||
putStrLn "simple-calc-example setup -- set up the profile"
|
||||
putStrLn
|
||||
"simple-calc-example kernel FILE -- run a kernel with FILE for communication with the frontend"
|
||||
putStrLn "simple-calc-example install -- set up the kernelspec"
|
||||
putStrLn "simple-calc-example kernel FILE -- run a kernel with FILE for communication with the frontend"
|
||||
|
83
ipython-kernel/examples/Simple.hs
Normal file
83
ipython-kernel/examples/Simple.hs
Normal file
@ -0,0 +1,83 @@
|
||||
module Simple where
|
||||
|
||||
import IHaskell.IPython.EasyKernel (easyKernel, installKernelspec)
|
||||
|
||||
functions :: [(String, Int -> Int -> Int)]
|
||||
functions = [("plus", (+)), ("minus", (-)), ("times", (*)), ("div", div), ("exp", (^))]
|
||||
|
||||
languageConfig :: LanguageInfo
|
||||
languageConfig = LanguageInfo
|
||||
{ languageName = "funcalc"
|
||||
, languageVersion = "1.0.0"
|
||||
, languageFileExtension = ".txt"
|
||||
, languageCodeMirrorMode = "null"
|
||||
}
|
||||
|
||||
languageKernelspec :: KernelSpec
|
||||
languageKernelspec = KernelSpec
|
||||
{ kernelDisplayName = "Calculator"
|
||||
, kernelLanguage = "calc"
|
||||
, kernelCommand = ["fun-calc-example", "kernel", "{connection_file}"]
|
||||
}
|
||||
|
||||
displayString :: String -> [DisplayData]
|
||||
displayString str = [DisplayData PlainText (T.pack str)]
|
||||
|
||||
languageCompletion :: Monad m => T.Text -> Int -> m (T.Text, [T.Text])
|
||||
languageCompletion code pos = return $
|
||||
let (before, _) = T.splitAt pos code
|
||||
word = last $ T.words $ T.map replace before
|
||||
in (word, map T.pack $ matches $ T.unpack word)
|
||||
|
||||
where
|
||||
matches :: String -> [String]
|
||||
matches word =
|
||||
case head word of
|
||||
'p' -> ["plus"]
|
||||
'm' -> ["minus"]
|
||||
'e' -> ["exp"]
|
||||
'd' -> ["div"]
|
||||
't' -> ["times"]
|
||||
|
||||
replace :: Char -> Char
|
||||
replace '(' = ' '
|
||||
replace ')' = ' '
|
||||
replace ',' = ' '
|
||||
replace x = x
|
||||
|
||||
languageInspect :: Monad m => T.Text -> Int -> m (Maybe DisplayData)
|
||||
languageInspect _ _ = return $ Just $ DisplayData PlainText $ T.pack $ unlines $
|
||||
[ "We support five arithmetic functions:"
|
||||
, " - plus +"
|
||||
, " - minus -"
|
||||
, " - div /"
|
||||
, " - times *"
|
||||
, " - exp ^"
|
||||
, "Expressions are written as f(exp, exp)"
|
||||
]
|
||||
|
||||
simpleConfig :: KernelConfig IO String String
|
||||
simpleConfig = KernelConfig
|
||||
{ kernelLanguageInfo = languageConfig
|
||||
, writeKernelspec = const $ return languageKernelspec
|
||||
, displayOutput = displayString
|
||||
, displayResult = displayString
|
||||
, completion = languageCompletion
|
||||
, inspectInfo = languageInspect
|
||||
, run = languageRun
|
||||
, debug = False
|
||||
}
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
args <- getArgs
|
||||
case args of
|
||||
["kernel", profileFile] ->
|
||||
easyKernel profileFile simpleConfig
|
||||
["install"] -> do
|
||||
putStrLn "Installing kernelspec..."
|
||||
installKernelspec simpleConfig False Nothing
|
||||
_ -> do
|
||||
putStrLn "Usage:"
|
||||
putStrLn "fun-calc-example install -- set up the kernelspec"
|
||||
putStrLn "fun-calc-example kernel FILE -- run a kernel with FILE for communication with the frontend"
|
@ -1,5 +1,5 @@
|
||||
name: ipython-kernel
|
||||
version: 0.7.0.0
|
||||
version: 0.8.0.0
|
||||
synopsis: A library for creating kernels for IPython frontends
|
||||
|
||||
description: ipython-kernel is a library for communicating with frontends for the interactive IPython framework. It is used extensively in IHaskell, the interactive Haskell environment.
|
||||
@ -40,9 +40,10 @@ library
|
||||
cereal >=0.3,
|
||||
containers >=0.5,
|
||||
directory >=1.1,
|
||||
temporary >=1.2,
|
||||
filepath >=1.2,
|
||||
process >=1.1,
|
||||
mtl >=2.1,
|
||||
tar >=0.4.0.1,
|
||||
text >=0.11,
|
||||
transformers >=0.3,
|
||||
uuid >=1.3,
|
||||
|
@ -9,46 +9,31 @@
|
||||
-- a simple language that nevertheless has side effects, global state, and timing effects is
|
||||
-- included in the examples directory.
|
||||
--
|
||||
-- = Profiles To run your kernel, you will need an IPython profile that causes the frontend to run
|
||||
-- it. To generate a fresh profile, run the command
|
||||
-- = Kernel Specs
|
||||
--
|
||||
-- > ipython profile create NAME
|
||||
-- To run your kernel, you will need to install the kernelspec into the Jupyter namespace.
|
||||
-- If your kernel name is `kernel`, you will need to run the command:
|
||||
--
|
||||
-- This will create a fresh IPython profile in @~\/.ipython\/profile_NAME@. This profile must be
|
||||
-- modified in two ways:
|
||||
-- > kernel install
|
||||
--
|
||||
-- 1. It needs to run your kernel instead of the default ipython 2. It must have message signing
|
||||
-- turned off, because 'easyKernel' doesn't support it
|
||||
--
|
||||
-- == Setting the executable To set the executable, modify the configuration object's
|
||||
-- @KernelManager.kernel_cmd@ property. For example:
|
||||
--
|
||||
-- > c.KernelManager.kernel_cmd = ['my_kernel', '{connection_file}']
|
||||
--
|
||||
-- Your own main should arrange to parse command line arguments such
|
||||
-- that the connection file is passed to easyKernel.
|
||||
--
|
||||
-- == Message signing
|
||||
-- To turn off message signing, use the following snippet:
|
||||
--
|
||||
-- > c.Session.key = b''
|
||||
-- > c.Session.keyfile = b''
|
||||
-- This will inform Jupyter of the kernel so that it may be used.
|
||||
--
|
||||
-- == Further profile improvements
|
||||
-- Consult the IPython documentation along with the generated profile
|
||||
-- source code for further configuration of the frontend, including
|
||||
-- syntax highlighting, logos, help text, and so forth.
|
||||
module IHaskell.IPython.EasyKernel (easyKernel, installProfile, KernelConfig(..)) where
|
||||
module IHaskell.IPython.EasyKernel (easyKernel, installKernelspec, KernelConfig(..)) where
|
||||
|
||||
import Data.Aeson (decode)
|
||||
import Data.Aeson (decode, encode)
|
||||
|
||||
import qualified Data.ByteString.Lazy as BL
|
||||
|
||||
import qualified Codec.Archive.Tar as Tar
|
||||
import System.IO.Temp (withTempDirectory)
|
||||
import System.Process (rawSystem)
|
||||
|
||||
import Control.Concurrent (MVar, readChan, writeChan, newMVar, readMVar, modifyMVar_)
|
||||
import Control.Monad.IO.Class (MonadIO(..))
|
||||
import Control.Monad (forever, when, unless)
|
||||
import Control.Monad (forever, when, unless, void)
|
||||
|
||||
import qualified Data.Map as Map
|
||||
import Data.Maybe (fromMaybe)
|
||||
@ -59,7 +44,7 @@ import IHaskell.IPython.Message.UUID as UUID
|
||||
import IHaskell.IPython.Types
|
||||
|
||||
import System.Directory (createDirectoryIfMissing, doesDirectoryExist, doesFileExist,
|
||||
getHomeDirectory)
|
||||
getHomeDirectory, getTemporaryDirectory)
|
||||
import System.FilePath ((</>))
|
||||
import System.Exit (exitSuccess)
|
||||
import System.IO (openFile, IOMode(ReadMode))
|
||||
@ -72,22 +57,20 @@ data KernelConfig m output result =
|
||||
{
|
||||
-- | Info on the language of the kernel.
|
||||
kernelLanguageInfo :: LanguageInfo
|
||||
-- | Determine the source of a profile to install using 'installProfile'. The source should be a
|
||||
-- tarball whose contents will be unpacked directly into the profile directory. For example, the
|
||||
-- file whose name is @ipython_config.py@ in the tar file for a language named @lang@ will end up in
|
||||
-- @~/.ipython/profile_lang/ipython_config.py@.
|
||||
, profileSource :: IO (Maybe FilePath)
|
||||
-- | Write all the files into the kernel directory, including `kernel.js`, `logo-64x64.png`, and any
|
||||
-- other required files. The directory to write to will be passed to this function, and the return
|
||||
-- value should be the kernelspec to be written to `kernel.json`.
|
||||
, writeKernelspec :: FilePath -> IO KernelSpec
|
||||
-- | How to render intermediate output
|
||||
, displayOutput :: output -> [DisplayData]
|
||||
-- | How to render final cell results
|
||||
, displayResult :: result -> [DisplayData]
|
||||
-- | Perform completion. The returned tuple consists of the matches, the matched text, and the
|
||||
-- completion text. The arguments are the code in the cell, the current line as text, and the column
|
||||
-- at which the cursor is placed.
|
||||
, completion :: T.Text -> T.Text -> Int -> Maybe ([T.Text], T.Text, T.Text)
|
||||
-- | Return the information or documentation for its argument. The returned tuple consists of the
|
||||
-- name, the documentation, and the type, respectively.
|
||||
, inspectInfo :: T.Text -> Maybe (T.Text, T.Text, T.Text)
|
||||
-- | Perform completion. The returned tuple consists of the matched text and completions. The
|
||||
-- arguments are the code in the cell and the position of the cursor in the cell.
|
||||
, completion :: T.Text -> Int -> m (T.Text, [T.Text])
|
||||
-- | Return the information or documentation for its argument, described by the cell contents and
|
||||
-- cursor position. The returned value is simply the data to display.
|
||||
, inspectInfo :: T.Text -> Int -> m (Maybe [DisplayData])
|
||||
-- | Execute a cell. The arguments are the contents of the cell, an IO action that will clear the
|
||||
-- current intermediate output, and an IO action that will add a new item to the intermediate
|
||||
-- output. The result consists of the actual result, the status to be sent to IPython, and the
|
||||
@ -97,34 +80,30 @@ data KernelConfig m output result =
|
||||
, debug :: Bool -- ^ Whether to print extra debugging information to
|
||||
}
|
||||
|
||||
-- the console | Attempt to install the IPython profile from the .tar file indicated by the
|
||||
-- 'profileSource' field of the configuration, if it is not already installed.
|
||||
installProfile :: MonadIO m => KernelConfig m output result -> m ()
|
||||
installProfile config = do
|
||||
installed <- isInstalled
|
||||
unless installed $ do
|
||||
profSrc <- liftIO $ profileSource config
|
||||
case profSrc of
|
||||
Nothing -> liftIO (putStrLn "No IPython profile is installed or specified")
|
||||
Just tar -> do
|
||||
profExists <- liftIO $ doesFileExist tar
|
||||
profTgt <- profDir
|
||||
if profExists
|
||||
then do
|
||||
liftIO $ createDirectoryIfMissing True profTgt
|
||||
liftIO $ Tar.extract profTgt tar
|
||||
else liftIO . putStrLn $
|
||||
"The supplied profile source '" ++ tar ++ "' does not exist"
|
||||
-- Install the kernelspec, using the `writeKernelspec` field of the kernel configuration.
|
||||
installKernelspec :: MonadIO m
|
||||
=> KernelConfig m output result -- ^ Kernel configuration to install
|
||||
-> Bool -- ^ Whether to use Jupyter `--replace`
|
||||
-> Maybe FilePath -- ^ (Optional) prefix to install into for Jupyter `--prefix`
|
||||
-> m ()
|
||||
installKernelspec config replace installPrefixMay =
|
||||
liftIO $ withTmpDir $ \tmp -> do
|
||||
let kernelDir = tmp </> languageName (kernelLanguageInfo config)
|
||||
createDirectoryIfMissing True kernelDir
|
||||
kernelSpec <- writeKernelspec config kernelDir
|
||||
|
||||
let filename = kernelDir </> "kernel.json"
|
||||
BL.writeFile filename $ encode $ toJSON kernelSpec
|
||||
|
||||
let replaceFlag = ["--replace" | replace]
|
||||
installPrefixFlag = maybe ["--user"] (\prefix -> ["--prefix", prefix]) installPrefixMay
|
||||
cmd = concat [["kernelspec", "install"], installPrefixFlag, [kernelDir], replaceFlag]
|
||||
void $ rawSystem "ipython" cmd
|
||||
|
||||
where
|
||||
profDir = do
|
||||
home <- liftIO getHomeDirectory
|
||||
return $ home </> ".ipython" </> ("profile_" ++ languageName (kernelLanguageInfo config))
|
||||
isInstalled = do
|
||||
prof <- profDir
|
||||
dirThere <- liftIO $ doesDirectoryExist prof
|
||||
isProf <- liftIO . doesFileExist $ prof </> "ipython_config.py"
|
||||
return $ dirThere && isProf
|
||||
withTmpDir act = do
|
||||
tmp <- getTemporaryDirectory
|
||||
withTempDirectory tmp "easyKernel" act
|
||||
|
||||
getProfile :: FilePath -> IO Profile
|
||||
getProfile fn = do
|
||||
@ -226,12 +205,27 @@ replyTo config execCount interface req@ExecuteRequest { getCode = code } replyHe
|
||||
, status = replyStatus
|
||||
}
|
||||
|
||||
replyTo config _ _ req@CompleteRequest{} replyHeader =
|
||||
-- TODO: FIX
|
||||
error "Completion: Unimplemented for IPython 3.0"
|
||||
replyTo config _ _ req@CompleteRequest{} replyHeader = do
|
||||
let code = getCode req
|
||||
pos = getCursorPos req
|
||||
(matchedText, completions) <- completion config code pos
|
||||
|
||||
replyTo _ _ _ InspectRequest{} _ =
|
||||
error "Inspection: Unimplemented for IPython 3.0"
|
||||
let start = pos - T.length matchedText
|
||||
end = pos
|
||||
reply = CompleteReply replyHeader completions start end Map.empty True
|
||||
return reply
|
||||
|
||||
replyTo config _ _ req@InspectRequest{} replyHeader = do
|
||||
result <- inspectInfo config (inspectCode req) (inspectCursorPos req)
|
||||
let reply =
|
||||
case result of
|
||||
Just datas -> InspectReply
|
||||
{ header = replyHeader
|
||||
, inspectStatus = True
|
||||
, inspectData = datas
|
||||
}
|
||||
_ -> InspectReply { header = replyHeader, inspectStatus = False, inspectData = [] }
|
||||
return reply
|
||||
|
||||
replyTo _ _ _ msg _ = do
|
||||
liftIO $ putStrLn "Unknown message: "
|
||||
|
Loading…
x
Reference in New Issue
Block a user