module Language.Drasil.Markdown.Config where
import Control.Lens((^.))
import Text.PrettyPrint (Doc, text, vcat, (<+>))
import System.FilePath (takeFileName)
import Drasil.Database.SearchTools (findAllLabelledContent)
import Language.Drasil (Document(Document), LabelledContent(LblC, _ctype),
RawContent(Figure), Sentence)
import Language.Drasil.Markdown.Print (pSpec)
import Language.Drasil.Printing.PrintingInformation (PrintingInformation, ckdb)
import Language.Drasil.Printing.Import.Sentence (spec)
import Language.Drasil.Printing.LayoutObj (Filepath)
import Utils.Drasil (makeCSV)
makeBook :: Document -> PrintingInformation -> Doc
makeBook :: Document -> PrintingInformation -> Doc
makeBook (Document Title
t Title
_ ShowTableOfContents
_ [Section]
_) PrintingInformation
sm = [Doc] -> Doc
vcat [
[Char] -> Doc
text [Char]
"[book]",
[Char] -> Doc
text [Char]
"language = \"en\"",
[Char] -> Doc
text [Char]
"multilingual = false",
[Char] -> Doc
text [Char]
"src = \"src\"",
[Char] -> Doc
text [Char]
"title =" Doc -> Doc -> Doc
<+> PrintingInformation -> Title -> Doc
mkTitle PrintingInformation
sm Title
t,
[Char] -> Doc
text [Char]
"[output.html]",
[Char] -> Doc
text [Char]
"smart-punctuation = true",
[Char] -> Doc
text [Char]
"mathjax-support = true"
]
makeBook Document
_ PrintingInformation
_ = [Char] -> Doc
forall a. HasCallStack => [Char] -> a
error [Char]
"Type not supported: Notebook."
makeRequirements :: PrintingInformation -> Doc
makeRequirements :: PrintingInformation -> Doc
makeRequirements PrintingInformation
sm = [[[Char]]] -> Doc
makeCSV ([[[Char]]] -> Doc) -> [[[Char]]] -> Doc
forall a b. (a -> b) -> a -> b
$ [[Char]
"Original", [Char]
"Copy"] [[Char]] -> [[[Char]]] -> [[[Char]]]
forall a. a -> [a] -> [a]
: PrintingInformation -> [[[Char]]]
assetMat PrintingInformation
sm
mkTitle :: PrintingInformation -> Sentence -> Doc
mkTitle :: PrintingInformation -> Title -> Doc
mkTitle PrintingInformation
sm Title
t = [Char] -> Doc
text [Char]
"\"" Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> RefMap -> Spec -> Doc
pSpec RefMap
forall a. Monoid a => a
mempty (PrintingInformation -> Title -> Spec
spec PrintingInformation
sm Title
t) Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> [Char] -> Doc
text [Char]
"\""
assetMat :: PrintingInformation -> [[Filepath]]
assetMat :: PrintingInformation -> [[[Char]]]
assetMat PrintingInformation
pinfo =
[[[Char]
fp, [Char]
"src/assets/" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
takeFileName [Char]
fp]
| LblC { _ctype :: LabelledContent -> RawContent
_ctype = Figure Title
_ [Char]
fp MaxWidthPercent
_ HasCaption
_ } <- ChunkDB -> [LabelledContent]
findAllLabelledContent (PrintingInformation
pinfo PrintingInformation
-> Getting ChunkDB PrintingInformation ChunkDB -> ChunkDB
forall s a. s -> Getting a s a -> a
^. Getting ChunkDB PrintingInformation ChunkDB
Lens' PrintingInformation ChunkDB
ckdb)]