Revert "Prepend jupyter_
to jupyter metadata keys."
This reverts commit 5eaff399d5
.
This commit is contained in:
parent
b08c8627d3
commit
7167330a2a
2 changed files with 0 additions and 12 deletions
|
@ -72,14 +72,8 @@ notebookToPandoc :: (PandocMonad m, FromJSON (Notebook a))
|
|||
notebookToPandoc opts notebook = do
|
||||
let cells = notebookCells notebook
|
||||
let (fmt,fmtminor) = notebookFormat notebook
|
||||
let jupyterMetaFields :: [String]
|
||||
jupyterMetaFields = ["kernelspec", "language_info", "toc"]
|
||||
let m = M.insert "nbformat" (MetaString $ show fmt) $
|
||||
M.insert "nbformat_minor" (MetaString $ show fmtminor) $
|
||||
-- mark jupyter fields specially so it doesn't trigger toc
|
||||
M.mapKeys (\k -> if k `elem` jupyterMetaFields
|
||||
then "jupyter_" <> k
|
||||
else k) $
|
||||
jsonMetaToMeta (notebookMetadata notebook)
|
||||
let lang = case M.lookup "kernelspec" m of
|
||||
Just (MetaMap ks) ->
|
||||
|
|
|
@ -38,7 +38,6 @@ import Prelude
|
|||
import Control.Monad.State
|
||||
import qualified Data.Map as M
|
||||
import Data.Maybe (catMaybes, fromMaybe)
|
||||
import Data.List (isPrefixOf)
|
||||
import Text.Pandoc.Options
|
||||
import Text.Pandoc.Definition
|
||||
import Data.Ipynb as Ipynb
|
||||
|
@ -79,11 +78,6 @@ pandocToNotebook opts (Pandoc meta blocks) = do
|
|||
let inlineWriter ils = T.stripEnd <$> writeMarkdown
|
||||
opts{ writerTemplate = Nothing } (Pandoc nullMeta [Plain ils])
|
||||
metadata' <- metaToJSON' blockWriter inlineWriter $
|
||||
(Meta .
|
||||
M.mapKeys (\k -> if "jupyter_" `isPrefixOf` k
|
||||
then drop 8 k
|
||||
else k) .
|
||||
unMeta) $
|
||||
B.deleteMeta "nbformat" $
|
||||
B.deleteMeta "nbformat_minor" $ meta
|
||||
let metadata = case fromJSON metadata' of
|
||||
|
|
Loading…
Reference in a new issue