switch to monad transformers (?)
This commit is contained in:
parent
e7d62f6adf
commit
a66e4ac022
|
@ -122,7 +122,6 @@ main = achille do
|
||||||
else do
|
else do
|
||||||
spath <- toAbsolute src
|
spath <- toAbsolute src
|
||||||
odir <- getOutputDir <&> (</> dropExtensions src)
|
odir <- getOutputDir <&> (</> dropExtensions src)
|
||||||
debug odir
|
|
||||||
tmp <- liftIO System.getTemporaryDirectory <&> (</> "escot")
|
tmp <- liftIO System.getTemporaryDirectory <&> (</> "escot")
|
||||||
|
|
||||||
liftIO $ System.createDirectoryIfMissing False tmp
|
liftIO $ System.createDirectoryIfMissing False tmp
|
||||||
|
@ -142,7 +141,6 @@ main = achille do
|
||||||
callCommand $ "cp " <> tmp <> "/* " <> odir
|
callCommand $ "cp " <> tmp <> "/* " <> odir
|
||||||
|
|
||||||
(meta@Note{..}, doc) <- readAbsPandocMetadataWith def {readerExtensions = pandocExtensions} (tmp </> "index.md")
|
(meta@Note{..}, doc) <- readAbsPandocMetadataWith def {readerExtensions = pandocExtensions} (tmp </> "index.md")
|
||||||
debug doc
|
|
||||||
path <- renderPandoc doc >>= write (dropExtensions src </> "index.html")
|
path <- renderPandoc doc >>= write (dropExtensions src </> "index.html")
|
||||||
. render index (KeyMap.insert "title" (String title) $ KeyMap.insert "nav" (String nav) $ KeyMap.empty)
|
. render index (KeyMap.insert "title" (String title) $ KeyMap.insert "nav" (String nav) $ KeyMap.empty)
|
||||||
return (takeDirectory path, meta)
|
return (takeDirectory path, meta)
|
||||||
|
|
|
@ -1,3 +1,4 @@
|
||||||
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
module Markdown where
|
module Markdown where
|
||||||
|
|
||||||
import Lucid
|
import Lucid
|
||||||
|
@ -5,29 +6,34 @@ import Lucid.Base (makeElement)
|
||||||
import Data.Text (pack)
|
import Data.Text (pack)
|
||||||
import Text.Pandoc.Builder
|
import Text.Pandoc.Builder
|
||||||
import Control.Monad (foldM)
|
import Control.Monad (foldM)
|
||||||
|
import Control.Monad.Trans
|
||||||
import Data.Functor ((<&>))
|
import Data.Functor ((<&>))
|
||||||
import Data.Bifoldable (Bifoldable, bifoldMap, bifoldrM)
|
import Data.Bifoldable (Bifoldable, bifoldMap, bifoldrM)
|
||||||
import Control.Monad.State.Strict
|
import Control.Monad.State.Strict
|
||||||
import Control.Monad.Identity
|
import Control.Monad.State.Class
|
||||||
|
import Control.Monad.Reader
|
||||||
|
import Control.Monad.Reader.Class
|
||||||
|
|
||||||
data MDState = MDState
|
data MDState = MDState
|
||||||
{ stNoteCount :: Int -- count of notes that HAVE been printed
|
{ stNoteCount :: Int -- count of notes that HAVE been printed
|
||||||
, stNotes :: [Html ()] -- notes that haven't be printed yet
|
, stNotes :: [Html ()] -- notes that haven't be printed yet
|
||||||
, stLevel :: Int -- block depth
|
|
||||||
}
|
}
|
||||||
|
|
||||||
defaultMDState :: MDState
|
defaultMDState :: MDState
|
||||||
defaultMDState = MDState
|
defaultMDState = MDState
|
||||||
{ stNoteCount = 0
|
{ stNoteCount = 0
|
||||||
, stNotes = []
|
, stNotes = []
|
||||||
, stLevel = 0
|
|
||||||
}
|
}
|
||||||
|
|
||||||
|
type BlockLevel = Int
|
||||||
|
|
||||||
render :: Pandoc -> Html ()
|
render :: Pandoc -> Html ()
|
||||||
render (Pandoc meta blocks) =
|
render (Pandoc meta blocks) =
|
||||||
fst $ runIdentity $ runStateT (blocksToHtml blocks) defaultMDState
|
fst $ runReader (runStateT (blocksToHtml blocks) defaultMDState) 0
|
||||||
|
|
||||||
inlineToHtml :: Monad m => Inline -> StateT MDState m (Html ())
|
inlineToHtml
|
||||||
|
:: (MonadState MDState m, MonadReader BlockLevel m)
|
||||||
|
=> Inline -> m (Html ())
|
||||||
inlineToHtml (Str str) = pure $ toHtml str
|
inlineToHtml (Str str) = pure $ toHtml str
|
||||||
inlineToHtml (Emph ins) = em_ <$> inlinesToHtml ins
|
inlineToHtml (Emph ins) = em_ <$> inlinesToHtml ins
|
||||||
inlineToHtml (Underline ins) = makeElement "u" <$> inlinesToHtml ins
|
inlineToHtml (Underline ins) = makeElement "u" <$> inlinesToHtml ins
|
||||||
|
@ -59,10 +65,14 @@ inlineToHtml (Note blocks) = do
|
||||||
pure $ a_ [href_ $ "#note" <> pack (show currentIdx)] $ "[" <> toHtml (show currentIdx) <> "]"
|
pure $ a_ [href_ $ "#note" <> pack (show currentIdx)] $ "[" <> toHtml (show currentIdx) <> "]"
|
||||||
inlineToHtml (Span attrs ins) = span_ <$> inlinesToHtml ins
|
inlineToHtml (Span attrs ins) = span_ <$> inlinesToHtml ins
|
||||||
|
|
||||||
inlinesToHtml :: Monad m => [Inline] -> StateT MDState m (Html ())
|
inlinesToHtml
|
||||||
|
:: (MonadState MDState m, MonadReader BlockLevel m)
|
||||||
|
=> [Inline] -> m (Html ())
|
||||||
inlinesToHtml = foldMapM inlineToHtml
|
inlinesToHtml = foldMapM inlineToHtml
|
||||||
|
|
||||||
blockToHtml :: Monad m => Block -> StateT MDState m (Html ())
|
blockToHtml
|
||||||
|
:: (MonadState MDState m, MonadReader BlockLevel m)
|
||||||
|
=> Block -> m (Html ())
|
||||||
blockToHtml (Plain ins) = pre_ <$> inlinesToHtml ins
|
blockToHtml (Plain ins) = pre_ <$> inlinesToHtml ins
|
||||||
blockToHtml (Para ins) = p_ <$> inlinesToHtml ins
|
blockToHtml (Para ins) = p_ <$> inlinesToHtml ins
|
||||||
blockToHtml (LineBlock ins) = undefined
|
blockToHtml (LineBlock ins) = undefined
|
||||||
|
@ -87,21 +97,19 @@ blockToHtml (Table attrs caption _ head rows foot) = pure mempty
|
||||||
blockToHtml (Div attrs blocks) = pure mempty
|
blockToHtml (Div attrs blocks) = pure mempty
|
||||||
blockToHtml Null = pure mempty
|
blockToHtml Null = pure mempty
|
||||||
|
|
||||||
blocksToHtml :: Monad m => [Block] -> StateT MDState m (Html ())
|
blocksToHtml
|
||||||
blocksToHtml = fmap mconcat . mapM renderBlock
|
:: (MonadState MDState m, MonadReader BlockLevel m)
|
||||||
where renderBlock :: Monad m => Block -> StateT MDState m (Html ())
|
=> [Block] -> m (Html ())
|
||||||
renderBlock block = do
|
blocksToHtml = foldMapM \block -> do
|
||||||
modify \s -> s { stLevel = stLevel s + 1 }
|
html <- local (+1) $ blockToHtml block
|
||||||
html <- blockToHtml block
|
lvl <- ask
|
||||||
MDState {..} <- get
|
|
||||||
let printingNotes = not (null stNotes) && stLevel == 1
|
|
||||||
|
|
||||||
let notes = when printingNotes (ol_ [class_ "footnotes", start_ $ pack (show $ stNoteCount + 1)] $ foldMap li_ (reverse stNotes))
|
MDState {..} <- get
|
||||||
when printingNotes $ modify \s -> s {stNoteCount = stNoteCount + length stNotes, stNotes = [] }
|
let shouldPrintNotes = not (null stNotes) && lvl == 0
|
||||||
|
let notes = when shouldPrintNotes (ol_ [class_ "footnotes", start_ $ pack (show $ stNoteCount + 1)] $ foldMap li_ (reverse stNotes))
|
||||||
|
when shouldPrintNotes $ modify \s -> s {stNoteCount = stNoteCount + length stNotes, stNotes = [] }
|
||||||
|
|
||||||
modify \s -> s { stLevel = stLevel - 1 }
|
pure $ html <> notes
|
||||||
|
|
||||||
pure $ html <> notes
|
|
||||||
|
|
||||||
foldMapM :: (Monad m, Monoid w, Foldable t) => (a -> m w) -> t a -> m w
|
foldMapM :: (Monad m, Monoid w, Foldable t) => (a -> m w) -> t a -> m w
|
||||||
foldMapM f = foldM (\acc a -> do
|
foldMapM f = foldM (\acc a -> do
|
||||||
|
|
Loading…
Reference in New Issue