module Text.Pandoc.SideNote (usingSideNotes) where
import Data.List (intercalate)
import Control.Monad.Gen
import Text.Pandoc.Walk (walk, walkM)
import Text.Pandoc.JSON
getFirstStr :: [Inline] -> Maybe String
getFirstStr [] = Nothing
getFirstStr (Str text : _) = Just text
getFirstStr (_ : inlines) = getFirstStr inlines
newline :: [Inline]
newline = [LineBreak, LineBreak]
coerceToInline :: [Block] -> [Inline]
coerceToInline = concatMap deBlock . walk deNote
where deBlock :: Block -> [Inline]
deBlock (Plain ls) = ls
deBlock (Para ls) = ls ++ newline
deBlock (LineBlock lss) = intercalate [LineBreak] lss ++ newline
deBlock (RawBlock fmt str) = [RawInline fmt str]
deBlock _ = []
deNote (Note _) = Str ""
deNote x = x
filterInline :: Inline -> Gen Int Inline
filterInline (Note blocks) = do
i <- gen
let content = coerceToInline blocks
let nonu = getFirstStr content == Just "{-}"
let content' = if nonu then tail content else content
let labelCls = "margin-toggle" ++ (if nonu then "" else " sidenote-number")
let labelSym = if nonu then "⊕" else ""
let labelHTML = "<label for=\"sn-" ++ show i ++ "\" class=\"" ++ labelCls ++ "\">" ++ labelSym ++ "</label>"
let label = RawInline (Format "html") labelHTML
let inputHTML = "<input type=\"checkbox\" id=\"sn-" ++ show i ++ "\" " ++ "class=\"margin-toggle\"/>"
let input = RawInline (Format "html") inputHTML
let (ident, _, attrs) = nullAttr
let noteTypeCls = if nonu then "marginnote" else "sidenote"
let note = Span (ident, [noteTypeCls], attrs) content'
return $ Span nullAttr [label, input, note]
filterInline inline = return inline
usingSideNotes :: Pandoc -> Pandoc
usingSideNotes (Pandoc meta blocks) = Pandoc meta (runGen (walkM filterInline blocks))