module Language.Drasil.Printing.Import.Document where
import Data.Map (fromList)
import Language.Drasil hiding (neg, sec, symbol, isIn, codeExpr)
import qualified Language.Drasil.Printing.AST as P
import qualified Language.Drasil.Printing.Citation as P
import qualified Language.Drasil.Printing.LayoutObj as T
import Language.Drasil.Printing.PrintingInformation
(PrintingInformation)
import Language.Drasil.Printing.Import.ModelExpr (modelExpr)
import Language.Drasil.Printing.Import.CodeExpr (codeExpr)
import Language.Drasil.Printing.Import.Sentence (spec)
import Control.Lens ((^.))
import Data.Bifunctor (bimap, second)
makeDocument :: PrintingInformation -> Document -> T.Document
makeDocument :: PrintingInformation -> Document -> Document
makeDocument PrintingInformation
sm (Document Title
titleLb Title
authorName ShowTableOfContents
_ [Section]
sections) =
Title -> Title -> [LayoutObj] -> Document
T.Document (PrintingInformation -> Title -> Title
spec PrintingInformation
sm Title
titleLb) (PrintingInformation -> Title -> Title
spec PrintingInformation
sm Title
authorName) (PrintingInformation -> [Section] -> [LayoutObj]
createLayout PrintingInformation
sm [Section]
sections)
makeDocument PrintingInformation
sm (Notebook Title
titleLb Title
authorName [Section]
sections) =
Title -> Title -> [LayoutObj] -> Document
T.Document (PrintingInformation -> Title -> Title
spec PrintingInformation
sm Title
titleLb) (PrintingInformation -> Title -> Title
spec PrintingInformation
sm Title
authorName) (PrintingInformation -> [Section] -> [LayoutObj]
createLayout' PrintingInformation
sm [Section]
sections)
makeProject :: PrintingInformation -> Document -> T.Project
makeProject :: PrintingInformation -> Document -> Project
makeProject PrintingInformation
_ Notebook {} = [Char] -> Project
forall a. HasCallStack => [Char] -> a
error [Char]
"Unsupported format: Notebook"
makeProject PrintingInformation
sm (Document Title
titleLb Title
authorName ShowTableOfContents
_ [Section]
sections) =
Title -> Title -> RefMap -> [File] -> Project
T.Project (PrintingInformation -> Title -> Title
spec PrintingInformation
sm Title
titleLb) (PrintingInformation -> Title -> Title
spec PrintingInformation
sm Title
authorName) RefMap
refMap [File]
files
where
files :: [File]
files = PrintingInformation -> [Section] -> [File]
createFiles PrintingInformation
sm [Section]
sections
refMap :: RefMap
refMap = [([Char], [Char])] -> RefMap
forall k a. Ord k => [(k, a)] -> Map k a
fromList ([([Char], [Char])] -> RefMap) -> [([Char], [Char])] -> RefMap
forall a b. (a -> b) -> a -> b
$ (File -> [([Char], [Char])]) -> [File] -> [([Char], [Char])]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap File -> [([Char], [Char])]
createRefMap' [File]
files
createFiles :: PrintingInformation -> [Section] -> [T.File]
createFiles :: PrintingInformation -> [Section] -> [File]
createFiles PrintingInformation
sm [Section]
secs = ((Int, Section) -> File) -> [(Int, Section)] -> [File]
forall a b. (a -> b) -> [a] -> [b]
map (PrintingInformation -> (Int, Section) -> File
file PrintingInformation
sm) [(Int, Section)]
secs'
where
secs' :: [(Int, Section)]
secs' = (Section -> [(Int, Section)]) -> [Section] -> [(Int, Section)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Int -> Section -> [(Int, Section)]
extractSubS Int
0) [Section]
secs
createRefMap' :: T.File -> [(String, T.Filename)]
createRefMap' :: File -> [([Char], [Char])]
createRefMap' (T.File Title
_ [Char]
l Int
_ [LayoutObj]
c) = (LayoutObj -> [([Char], [Char])])
-> [LayoutObj] -> [([Char], [Char])]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ([Char] -> LayoutObj -> [([Char], [Char])]
createRefMap [Char]
l) [LayoutObj]
c
createRefMap :: T.Filename -> T.LayoutObj -> [(String, T.Filename)]
createRefMap :: [Char] -> LayoutObj -> [([Char], [Char])]
createRefMap [Char]
fn (T.Header Int
_ Title
_ Title
l) = [Char] -> Title -> [([Char], [Char])]
createRef [Char]
fn Title
l
createRefMap [Char]
fn (T.HDiv Tags
_ [LayoutObj]
_ Title
l) = [Char] -> Title -> [([Char], [Char])]
createRef [Char]
fn Title
l
createRefMap [Char]
fn (T.Table Tags
_ [[Title]]
_ Title
l Bool
_ Title
_) = [Char] -> Title -> [([Char], [Char])]
createRef [Char]
fn Title
l
createRefMap [Char]
fn (T.Definition DType
_ [([Char], [LayoutObj])]
_ Title
l) = [Char] -> Title -> [([Char], [Char])]
createRef [Char]
fn Title
l
createRefMap [Char]
fn (T.List ListType
t) = ListType -> [([Char], [Char])]
pass ListType
t
where
pass :: ListType -> [([Char], [Char])]
pass (P.Ordered [(ItemType, Maybe Title)]
ls) = [(ItemType, Maybe Title)] -> [([Char], [Char])]
forall {a}. [(a, Maybe Title)] -> [([Char], [Char])]
process [(ItemType, Maybe Title)]
ls
pass (P.Unordered [(ItemType, Maybe Title)]
ls) = [(ItemType, Maybe Title)] -> [([Char], [Char])]
forall {a}. [(a, Maybe Title)] -> [([Char], [Char])]
process [(ItemType, Maybe Title)]
ls
pass (P.Simple [(Title, ItemType, Maybe Title)]
ls) = [(Title, ItemType, Maybe Title)] -> [([Char], [Char])]
forall {a} {b}. [(a, b, Maybe Title)] -> [([Char], [Char])]
process' [(Title, ItemType, Maybe Title)]
ls
pass (P.Desc [(Title, ItemType, Maybe Title)]
ls) = [(Title, ItemType, Maybe Title)] -> [([Char], [Char])]
forall {a} {b}. [(a, b, Maybe Title)] -> [([Char], [Char])]
process' [(Title, ItemType, Maybe Title)]
ls
pass (P.Definitions [(Title, ItemType, Maybe Title)]
ls) = [(Title, ItemType, Maybe Title)] -> [([Char], [Char])]
forall {a} {b}. [(a, b, Maybe Title)] -> [([Char], [Char])]
process' [(Title, ItemType, Maybe Title)]
ls
process :: [(a, Maybe Title)] -> [([Char], [Char])]
process = ((a, Maybe Title) -> [([Char], [Char])])
-> [(a, Maybe Title)] -> [([Char], [Char])]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\(a
_, Maybe Title
l) -> [([Char], [Char])]
-> (Title -> [([Char], [Char])])
-> Maybe Title
-> [([Char], [Char])]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] ([Char] -> Title -> [([Char], [Char])]
createRef [Char]
fn) Maybe Title
l)
process' :: [(a, b, Maybe Title)] -> [([Char], [Char])]
process' = ((a, b, Maybe Title) -> [([Char], [Char])])
-> [(a, b, Maybe Title)] -> [([Char], [Char])]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\(a
_, b
_, Maybe Title
l) -> [([Char], [Char])]
-> (Title -> [([Char], [Char])])
-> Maybe Title
-> [([Char], [Char])]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] ([Char] -> Title -> [([Char], [Char])]
createRef [Char]
fn) Maybe Title
l)
createRefMap [Char]
fn (T.Figure Title
l Maybe Title
_ [Char]
_ MaxWidthPercent
_) = [Char] -> Title -> [([Char], [Char])]
createRef [Char]
fn Title
l
createRefMap [Char]
fn (T.Bib BibRef
ls) = (Citation -> ([Char], [Char])) -> BibRef -> [([Char], [Char])]
forall a b. (a -> b) -> [a] -> [b]
map Citation -> ([Char], [Char])
bibRefs BibRef
ls
where
bibRefs :: Citation -> ([Char], [Char])
bibRefs (P.Cite [Char]
l CitationKind
_ [CiteField]
_) = ([Char]
l, [Char]
fn)
createRefMap [Char]
_ LayoutObj
_ = []
createRef :: T.Filename -> P.Label -> [(String, T.Filename)]
createRef :: [Char] -> Title -> [([Char], [Char])]
createRef [Char]
fn (P.S [Char]
l) = [([Char]
l, [Char]
fn)]
createRef [Char]
_ Title
_ = []
createLayout :: PrintingInformation -> [Section] -> [T.LayoutObj]
createLayout :: PrintingInformation -> [Section] -> [LayoutObj]
createLayout PrintingInformation
sm = (Section -> LayoutObj) -> [Section] -> [LayoutObj]
forall a b. (a -> b) -> [a] -> [b]
map (PrintingInformation -> Int -> Section -> LayoutObj
sec PrintingInformation
sm Int
0)
createLayout' :: PrintingInformation -> [Section] -> [T.LayoutObj]
createLayout' :: PrintingInformation -> [Section] -> [LayoutObj]
createLayout' PrintingInformation
sm = (Section -> LayoutObj) -> [Section] -> [LayoutObj]
forall a b. (a -> b) -> [a] -> [b]
map (PrintingInformation -> Int -> Section -> LayoutObj
cel PrintingInformation
sm Int
0)
extractSubS :: Int -> Section -> [(T.Depth, Section)]
Int
d x :: Section
x@(Section Title
tl [SecCons]
c Reference
r)
| Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1 = [(Int
d, Section
x)]
| Bool
otherwise = (Int
d, Title -> [SecCons] -> Reference -> Section
Section Title
tl ((SecCons -> Bool) -> [SecCons] -> [SecCons]
forall a. (a -> Bool) -> [a] -> [a]
filter SecCons -> Bool
isCon [SecCons]
c) Reference
r) (Int, Section) -> [(Int, Section)] -> [(Int, Section)]
forall a. a -> [a] -> [a]
:
(SecCons -> [(Int, Section)]) -> [SecCons] -> [(Int, Section)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Int -> SecCons -> [(Int, Section)]
sepSub (Int
d Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)) [SecCons]
c
where
isCon :: SecCons -> Bool
isCon (Con Contents
_) = Bool
True
isCon SecCons
_ = Bool
False
sepSub :: Int -> SecCons -> [(Int, Section)]
sepSub Int
_ (Con Contents
_) = []
sepSub Int
dep (Sub Section
s) = Int -> Section -> [(Int, Section)]
extractSubS Int
dep Section
s
file :: PrintingInformation -> (T.Depth, Section) -> T.File
file :: PrintingInformation -> (Int, Section) -> File
file PrintingInformation
sm (Int
d, x :: Section
x@(Section Title
titleLb [SecCons]
contents Reference
_)) =
Title -> [Char] -> Int -> [LayoutObj] -> File
T.File (PrintingInformation -> Title -> Title
spec PrintingInformation
sm Title
titleLb) [Char]
fn Int
d [LayoutObj]
los
where
refr :: [Char]
refr = Section -> [Char]
forall s. Referable s => s -> [Char]
refAdd Section
x
fn :: [Char]
fn = (Char -> Bool) -> [Char] -> [Char]
forall a. (a -> Bool) -> [a] -> [a]
filter (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
':') [Char]
refr
los :: [LayoutObj]
los = Int -> Title -> Title -> LayoutObj
T.Header Int
d (PrintingInformation -> Title -> Title
spec PrintingInformation
sm Title
titleLb) ([Char] -> Title
P.S [Char]
refr) LayoutObj -> [LayoutObj] -> [LayoutObj]
forall a. a -> [a] -> [a]
:
(SecCons -> LayoutObj) -> [SecCons] -> [LayoutObj]
forall a b. (a -> b) -> [a] -> [b]
map (PrintingInformation -> Int -> SecCons -> LayoutObj
layout PrintingInformation
sm Int
d) [SecCons]
contents
sec :: PrintingInformation -> Int -> Section -> T.LayoutObj
sec :: PrintingInformation -> Int -> Section -> LayoutObj
sec PrintingInformation
sm Int
depth x :: Section
x@(Section Title
titleLb [SecCons]
contents Reference
_) =
let refr :: Title
refr = [Char] -> Title
P.S (Section -> [Char]
forall s. Referable s => s -> [Char]
refAdd Section
x) in
Tags -> [LayoutObj] -> Title -> LayoutObj
T.HDiv [Tags -> [Char]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat (Int -> [Char] -> Tags
forall a. Int -> a -> [a]
replicate Int
depth [Char]
"sub") [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"section"]
(Int -> Title -> Title -> LayoutObj
T.Header Int
depth (PrintingInformation -> Title -> Title
spec PrintingInformation
sm Title
titleLb) Title
refr LayoutObj -> [LayoutObj] -> [LayoutObj]
forall a. a -> [a] -> [a]
:
(SecCons -> LayoutObj) -> [SecCons] -> [LayoutObj]
forall a b. (a -> b) -> [a] -> [b]
map (PrintingInformation -> Int -> SecCons -> LayoutObj
layout PrintingInformation
sm Int
depth) [SecCons]
contents) Title
refr
cel :: PrintingInformation -> Int -> Section -> T.LayoutObj
cel :: PrintingInformation -> Int -> Section -> LayoutObj
cel PrintingInformation
sm Int
depth x :: Section
x@(Section Title
titleLb [SecCons]
contents Reference
_) =
let refr :: Title
refr = [Char] -> Title
P.S (Section -> [Char]
forall s. Referable s => s -> [Char]
refAdd Section
x) in
[LayoutObj] -> LayoutObj
T.Cell (Int -> Title -> Title -> LayoutObj
T.Header Int
depth (PrintingInformation -> Title -> Title
spec PrintingInformation
sm Title
titleLb) Title
refr LayoutObj -> [LayoutObj] -> [LayoutObj]
forall a. a -> [a] -> [a]
:
(SecCons -> LayoutObj) -> [SecCons] -> [LayoutObj]
forall a b. (a -> b) -> [a] -> [b]
map (PrintingInformation -> Int -> SecCons -> LayoutObj
layout PrintingInformation
sm Int
depth) [SecCons]
contents)
layout :: PrintingInformation -> Int -> SecCons -> T.LayoutObj
layout :: PrintingInformation -> Int -> SecCons -> LayoutObj
layout PrintingInformation
sm Int
currDepth (Sub Section
s) = PrintingInformation -> Int -> Section -> LayoutObj
sec PrintingInformation
sm (Int
currDepthInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) Section
s
layout PrintingInformation
sm Int
_ (Con Contents
c) = PrintingInformation -> Contents -> LayoutObj
lay PrintingInformation
sm Contents
c
lay :: PrintingInformation -> Contents -> T.LayoutObj
lay :: PrintingInformation -> Contents -> LayoutObj
lay PrintingInformation
sm (LlC LabelledContent
x) = PrintingInformation -> LabelledContent -> LayoutObj
layLabelled PrintingInformation
sm LabelledContent
x
lay PrintingInformation
sm (UlC UnlabelledContent
x) = PrintingInformation -> RawContent -> LayoutObj
layUnlabelled PrintingInformation
sm (UnlabelledContent
x UnlabelledContent
-> Getting RawContent UnlabelledContent RawContent -> RawContent
forall s a. s -> Getting a s a -> a
^. Getting RawContent UnlabelledContent RawContent
forall c. HasContents c => Lens' c RawContent
Lens' UnlabelledContent RawContent
accessContents)
layLabelled :: PrintingInformation -> LabelledContent -> T.LayoutObj
layLabelled :: PrintingInformation -> LabelledContent -> LayoutObj
layLabelled PrintingInformation
sm x :: LabelledContent
x@(LblC Reference
_ (Table [Title]
hdr [[Title]]
lls Title
t Bool
b)) = Tags -> [[Title]] -> Title -> Bool -> Title -> LayoutObj
T.Table [[Char]
"table"]
((Title -> Title) -> [Title] -> [Title]
forall a b. (a -> b) -> [a] -> [b]
map (PrintingInformation -> Title -> Title
spec PrintingInformation
sm) [Title]
hdr [Title] -> [[Title]] -> [[Title]]
forall a. a -> [a] -> [a]
: ([Title] -> [Title]) -> [[Title]] -> [[Title]]
forall a b. (a -> b) -> [a] -> [b]
map ((Title -> Title) -> [Title] -> [Title]
forall a b. (a -> b) -> [a] -> [b]
map (PrintingInformation -> Title -> Title
spec PrintingInformation
sm)) [[Title]]
lls)
([Char] -> Title
P.S ([Char] -> Title) -> [Char] -> Title
forall a b. (a -> b) -> a -> b
$ LblType -> [Char]
getAdd (LblType -> [Char]) -> LblType -> [Char]
forall a b. (a -> b) -> a -> b
$ LabelledContent -> LblType
forall b. HasRefAddress b => b -> LblType
getRefAdd LabelledContent
x)
Bool
b (PrintingInformation -> Title -> Title
spec PrintingInformation
sm Title
t)
layLabelled PrintingInformation
sm x :: LabelledContent
x@(LblC Reference
_ (EqnBlock ModelExpr
c)) = Tags -> [LayoutObj] -> Title -> LayoutObj
T.HDiv [[Char]
"equation"]
[Title -> LayoutObj
T.EqnBlock (Expr -> Title
P.E (ModelExpr -> PrintingInformation -> Expr
modelExpr ModelExpr
c PrintingInformation
sm))]
([Char] -> Title
P.S ([Char] -> Title) -> [Char] -> Title
forall a b. (a -> b) -> a -> b
$ LblType -> [Char]
getAdd (LblType -> [Char]) -> LblType -> [Char]
forall a b. (a -> b) -> a -> b
$ LabelledContent -> LblType
forall b. HasRefAddress b => b -> LblType
getRefAdd LabelledContent
x)
layLabelled PrintingInformation
sm x :: LabelledContent
x@(LblC Reference
_ (Figure Title
c [Char]
f MaxWidthPercent
wp HasCaption
hc)) = Title -> Maybe Title -> [Char] -> MaxWidthPercent -> LayoutObj
T.Figure
([Char] -> Title
P.S ([Char] -> Title) -> [Char] -> Title
forall a b. (a -> b) -> a -> b
$ LblType -> [Char]
getAdd (LblType -> [Char]) -> LblType -> [Char]
forall a b. (a -> b) -> a -> b
$ LabelledContent -> LblType
forall b. HasRefAddress b => b -> LblType
getRefAdd LabelledContent
x)
(if HasCaption
hc HasCaption -> HasCaption -> Bool
forall a. Eq a => a -> a -> Bool
== HasCaption
WithCaption then Title -> Maybe Title
forall a. a -> Maybe a
Just (PrintingInformation -> Title -> Title
spec PrintingInformation
sm Title
c) else Maybe Title
forall a. Maybe a
Nothing)
[Char]
f MaxWidthPercent
wp
layLabelled PrintingInformation
sm x :: LabelledContent
x@(LblC Reference
_ (Graph [(Title, Title)]
ps Maybe MaxWidthPercent
w Maybe MaxWidthPercent
h Title
t)) = [(Title, Title)]
-> Maybe MaxWidthPercent
-> Maybe MaxWidthPercent
-> Title
-> Title
-> LayoutObj
T.Graph
(((Title, Title) -> (Title, Title))
-> [(Title, Title)] -> [(Title, Title)]
forall a b. (a -> b) -> [a] -> [b]
map ((Title -> Title)
-> (Title -> Title) -> (Title, Title) -> (Title, Title)
forall a b c d. (a -> b) -> (c -> d) -> (a, c) -> (b, d)
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap (PrintingInformation -> Title -> Title
spec PrintingInformation
sm) (PrintingInformation -> Title -> Title
spec PrintingInformation
sm)) [(Title, Title)]
ps) Maybe MaxWidthPercent
w Maybe MaxWidthPercent
h (PrintingInformation -> Title -> Title
spec PrintingInformation
sm Title
t)
([Char] -> Title
P.S ([Char] -> Title) -> [Char] -> Title
forall a b. (a -> b) -> a -> b
$ LblType -> [Char]
getAdd (LblType -> [Char]) -> LblType -> [Char]
forall a b. (a -> b) -> a -> b
$ LabelledContent -> LblType
forall b. HasRefAddress b => b -> LblType
getRefAdd LabelledContent
x)
layLabelled PrintingInformation
sm x :: LabelledContent
x@(LblC Reference
_ (Defini DType
dtyp [([Char], [Contents])]
pairs)) = DType -> [([Char], [LayoutObj])] -> Title -> LayoutObj
T.Definition
DType
dtyp ([([Char], [Contents])] -> [([Char], [LayoutObj])]
forall {a}. [(a, [Contents])] -> [(a, [LayoutObj])]
layPairs [([Char], [Contents])]
pairs)
([Char] -> Title
P.S ([Char] -> Title) -> [Char] -> Title
forall a b. (a -> b) -> a -> b
$ LblType -> [Char]
getAdd (LblType -> [Char]) -> LblType -> [Char]
forall a b. (a -> b) -> a -> b
$ LabelledContent -> LblType
forall b. HasRefAddress b => b -> LblType
getRefAdd LabelledContent
x)
where layPairs :: [(a, [Contents])] -> [(a, [LayoutObj])]
layPairs = ((a, [Contents]) -> (a, [LayoutObj]))
-> [(a, [Contents])] -> [(a, [LayoutObj])]
forall a b. (a -> b) -> [a] -> [b]
map (([Contents] -> [LayoutObj]) -> (a, [Contents]) -> (a, [LayoutObj])
forall b c a. (b -> c) -> (a, b) -> (a, c)
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second ((Contents -> LayoutObj) -> [Contents] -> [LayoutObj]
forall a b. (a -> b) -> [a] -> [b]
map (PrintingInformation -> Contents -> LayoutObj
lay PrintingInformation
sm)))
layLabelled PrintingInformation
sm (LblC Reference
_ (Paragraph Title
c)) = Title -> LayoutObj
T.Paragraph (PrintingInformation -> Title -> Title
spec PrintingInformation
sm Title
c)
layLabelled PrintingInformation
sm x :: LabelledContent
x@(LblC Reference
_ (DerivBlock Title
h [RawContent]
d)) = Tags -> [LayoutObj] -> Title -> LayoutObj
T.HDiv [[Char]
"subsubsubsection"]
(Int -> Title -> Title -> LayoutObj
T.Header Int
3 (PrintingInformation -> Title -> Title
spec PrintingInformation
sm Title
h) Title
refr LayoutObj -> [LayoutObj] -> [LayoutObj]
forall a. a -> [a] -> [a]
: (RawContent -> LayoutObj) -> [RawContent] -> [LayoutObj]
forall a b. (a -> b) -> [a] -> [b]
map (PrintingInformation -> RawContent -> LayoutObj
layUnlabelled PrintingInformation
sm) [RawContent]
d) Title
refr
where refr :: Title
refr = [Char] -> Title
P.S ([Char] -> Title) -> [Char] -> Title
forall a b. (a -> b) -> a -> b
$ LabelledContent -> [Char]
forall s. Referable s => s -> [Char]
refAdd LabelledContent
x [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"Deriv"
layLabelled PrintingInformation
sm (LblC Reference
_ (Enumeration ListType
cs)) = ListType -> LayoutObj
T.List (ListType -> LayoutObj) -> ListType -> LayoutObj
forall a b. (a -> b) -> a -> b
$ PrintingInformation -> ListType -> ListType
makeL PrintingInformation
sm ListType
cs
layLabelled PrintingInformation
_ (LblC Reference
_ (Bib BibRef
bib)) = BibRef -> LayoutObj
T.Bib (BibRef -> LayoutObj) -> BibRef -> LayoutObj
forall a b. (a -> b) -> a -> b
$ (Citation -> Citation) -> BibRef -> BibRef
forall a b. (a -> b) -> [a] -> [b]
map Citation -> Citation
layCite BibRef
bib
layLabelled PrintingInformation
sm (LblC Reference
_ (CodeBlock CodeExpr
c)) = Title -> LayoutObj
T.CodeBlock (Expr -> Title
P.E (CodeExpr -> PrintingInformation -> Expr
codeExpr CodeExpr
c PrintingInformation
sm))
layUnlabelled :: PrintingInformation -> RawContent -> T.LayoutObj
layUnlabelled :: PrintingInformation -> RawContent -> LayoutObj
layUnlabelled PrintingInformation
sm (Table [Title]
hdr [[Title]]
lls Title
t Bool
b) = Tags -> [[Title]] -> Title -> Bool -> Title -> LayoutObj
T.Table [[Char]
"table"]
((Title -> Title) -> [Title] -> [Title]
forall a b. (a -> b) -> [a] -> [b]
map (PrintingInformation -> Title -> Title
spec PrintingInformation
sm) [Title]
hdr [Title] -> [[Title]] -> [[Title]]
forall a. a -> [a] -> [a]
: ([Title] -> [Title]) -> [[Title]] -> [[Title]]
forall a b. (a -> b) -> [a] -> [b]
map ((Title -> Title) -> [Title] -> [Title]
forall a b. (a -> b) -> [a] -> [b]
map (PrintingInformation -> Title -> Title
spec PrintingInformation
sm)) [[Title]]
lls) ([Char] -> Title
P.S [Char]
"nolabel0") Bool
b (PrintingInformation -> Title -> Title
spec PrintingInformation
sm Title
t)
layUnlabelled PrintingInformation
sm (Paragraph Title
c) = Title -> LayoutObj
T.Paragraph (PrintingInformation -> Title -> Title
spec PrintingInformation
sm Title
c)
layUnlabelled PrintingInformation
sm (EqnBlock ModelExpr
c) = Tags -> [LayoutObj] -> Title -> LayoutObj
T.HDiv [[Char]
"equation"] [Title -> LayoutObj
T.EqnBlock (Expr -> Title
P.E (ModelExpr -> PrintingInformation -> Expr
modelExpr ModelExpr
c PrintingInformation
sm))] Title
P.EmptyS
layUnlabelled PrintingInformation
sm (DerivBlock Title
h [RawContent]
d) = Tags -> [LayoutObj] -> Title -> LayoutObj
T.HDiv [[Char]
"subsubsubsection"]
(Int -> Title -> Title -> LayoutObj
T.Header Int
3 (PrintingInformation -> Title -> Title
spec PrintingInformation
sm Title
h) Title
refr LayoutObj -> [LayoutObj] -> [LayoutObj]
forall a. a -> [a] -> [a]
: (RawContent -> LayoutObj) -> [RawContent] -> [LayoutObj]
forall a b. (a -> b) -> [a] -> [b]
map (PrintingInformation -> RawContent -> LayoutObj
layUnlabelled PrintingInformation
sm) [RawContent]
d) Title
refr
where refr :: Title
refr = [Char] -> Title
P.S [Char]
"nolabel1"
layUnlabelled PrintingInformation
sm (Enumeration ListType
cs) = ListType -> LayoutObj
T.List (ListType -> LayoutObj) -> ListType -> LayoutObj
forall a b. (a -> b) -> a -> b
$ PrintingInformation -> ListType -> ListType
makeL PrintingInformation
sm ListType
cs
layUnlabelled PrintingInformation
sm (Figure Title
c [Char]
f MaxWidthPercent
wp HasCaption
hc) = Title -> Maybe Title -> [Char] -> MaxWidthPercent -> LayoutObj
T.Figure ([Char] -> Title
P.S [Char]
"nolabel2")
(if HasCaption
hc HasCaption -> HasCaption -> Bool
forall a. Eq a => a -> a -> Bool
== HasCaption
WithCaption then Title -> Maybe Title
forall a. a -> Maybe a
Just (PrintingInformation -> Title -> Title
spec PrintingInformation
sm Title
c) else Maybe Title
forall a. Maybe a
Nothing) [Char]
f MaxWidthPercent
wp
layUnlabelled PrintingInformation
sm (Graph [(Title, Title)]
ps Maybe MaxWidthPercent
w Maybe MaxWidthPercent
h Title
t) = [(Title, Title)]
-> Maybe MaxWidthPercent
-> Maybe MaxWidthPercent
-> Title
-> Title
-> LayoutObj
T.Graph (((Title, Title) -> (Title, Title))
-> [(Title, Title)] -> [(Title, Title)]
forall a b. (a -> b) -> [a] -> [b]
map ((Title -> Title)
-> (Title -> Title) -> (Title, Title) -> (Title, Title)
forall a b c d. (a -> b) -> (c -> d) -> (a, c) -> (b, d)
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap (PrintingInformation -> Title -> Title
spec PrintingInformation
sm) (PrintingInformation -> Title -> Title
spec PrintingInformation
sm)) [(Title, Title)]
ps)
Maybe MaxWidthPercent
w Maybe MaxWidthPercent
h (PrintingInformation -> Title -> Title
spec PrintingInformation
sm Title
t) ([Char] -> Title
P.S [Char]
"nolabel6")
layUnlabelled PrintingInformation
sm (Defini DType
dtyp [([Char], [Contents])]
pairs) = DType -> [([Char], [LayoutObj])] -> Title -> LayoutObj
T.Definition DType
dtyp ([([Char], [Contents])] -> [([Char], [LayoutObj])]
forall {a}. [(a, [Contents])] -> [(a, [LayoutObj])]
layPairs [([Char], [Contents])]
pairs) ([Char] -> Title
P.S [Char]
"nolabel7")
where layPairs :: [(a, [Contents])] -> [(a, [LayoutObj])]
layPairs = ((a, [Contents]) -> (a, [LayoutObj]))
-> [(a, [Contents])] -> [(a, [LayoutObj])]
forall a b. (a -> b) -> [a] -> [b]
map (([Contents] -> [LayoutObj]) -> (a, [Contents]) -> (a, [LayoutObj])
forall b c a. (b -> c) -> (a, b) -> (a, c)
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second ((Contents -> LayoutObj) -> [Contents] -> [LayoutObj]
forall a b. (a -> b) -> [a] -> [b]
map Contents -> LayoutObj
forall {s}. HasContents s => s -> LayoutObj
temp))
temp :: s -> LayoutObj
temp s
y = PrintingInformation -> RawContent -> LayoutObj
layUnlabelled PrintingInformation
sm (s
y s -> Getting RawContent s RawContent -> RawContent
forall s a. s -> Getting a s a -> a
^. Getting RawContent s RawContent
forall c. HasContents c => Lens' c RawContent
Lens' s RawContent
accessContents)
layUnlabelled PrintingInformation
_ (Bib BibRef
bib) = BibRef -> LayoutObj
T.Bib (BibRef -> LayoutObj) -> BibRef -> LayoutObj
forall a b. (a -> b) -> a -> b
$ (Citation -> Citation) -> BibRef -> BibRef
forall a b. (a -> b) -> [a] -> [b]
map Citation -> Citation
layCite BibRef
bib
layUnlabelled PrintingInformation
sm (CodeBlock CodeExpr
c) = Title -> LayoutObj
T.CodeBlock (Expr -> Title
P.E (CodeExpr -> PrintingInformation -> Expr
codeExpr CodeExpr
c PrintingInformation
sm))
layCite :: Citation -> P.Citation
layCite :: Citation -> Citation
layCite Citation
c = [Char] -> CitationKind -> [CiteField] -> Citation
P.Cite (Citation -> [Char]
forall a. HasUID a => a -> [Char]
showUID Citation
c) (Citation
c Citation
-> Getting CitationKind Citation CitationKind -> CitationKind
forall s a. s -> Getting a s a -> a
^. Getting CitationKind Citation CitationKind
Lens' Citation CitationKind
citeKind) ((CiteField -> CiteField) -> [CiteField] -> [CiteField]
forall a b. (a -> b) -> [a] -> [b]
map CiteField -> CiteField
layField (Citation
c Citation -> Getting [CiteField] Citation [CiteField] -> [CiteField]
forall s a. s -> Getting a s a -> a
^. Getting [CiteField] Citation [CiteField]
forall c. HasFields c => Lens' c [CiteField]
Lens' Citation [CiteField]
getFields))
layField :: CiteField -> P.CiteField
layField :: CiteField -> CiteField
layField (Address [Char]
s) = Title -> CiteField
P.Address (Title -> CiteField) -> Title -> CiteField
forall a b. (a -> b) -> a -> b
$ [Char] -> Title
P.S [Char]
s
layField (Author People
p) = People -> CiteField
P.Author People
p
layField (BookTitle [Char]
b) = Title -> CiteField
P.BookTitle (Title -> CiteField) -> Title -> CiteField
forall a b. (a -> b) -> a -> b
$ [Char] -> Title
P.S [Char]
b
layField (Chapter Int
c) = Int -> CiteField
P.Chapter Int
c
layField (Edition Int
e) = Int -> CiteField
P.Edition Int
e
layField (Editor People
e) = People -> CiteField
P.Editor People
e
layField (Institution [Char]
i) = Title -> CiteField
P.Institution (Title -> CiteField) -> Title -> CiteField
forall a b. (a -> b) -> a -> b
$ [Char] -> Title
P.S [Char]
i
layField (Journal [Char]
j) = Title -> CiteField
P.Journal (Title -> CiteField) -> Title -> CiteField
forall a b. (a -> b) -> a -> b
$ [Char] -> Title
P.S [Char]
j
layField (Month Month
m) = Month -> CiteField
P.Month Month
m
layField (Note [Char]
n) = Title -> CiteField
P.Note (Title -> CiteField) -> Title -> CiteField
forall a b. (a -> b) -> a -> b
$ [Char] -> Title
P.S [Char]
n
layField (Number Int
n) = Int -> CiteField
P.Number Int
n
layField (Organization [Char]
o) = Title -> CiteField
P.Organization (Title -> CiteField) -> Title -> CiteField
forall a b. (a -> b) -> a -> b
$ [Char] -> Title
P.S [Char]
o
layField (Pages [Int]
p) = [Int] -> CiteField
P.Pages [Int]
p
layField (Publisher [Char]
p) = Title -> CiteField
P.Publisher (Title -> CiteField) -> Title -> CiteField
forall a b. (a -> b) -> a -> b
$ [Char] -> Title
P.S [Char]
p
layField (School [Char]
s) = Title -> CiteField
P.School (Title -> CiteField) -> Title -> CiteField
forall a b. (a -> b) -> a -> b
$ [Char] -> Title
P.S [Char]
s
layField (Series [Char]
s) = Title -> CiteField
P.Series (Title -> CiteField) -> Title -> CiteField
forall a b. (a -> b) -> a -> b
$ [Char] -> Title
P.S [Char]
s
layField (Title [Char]
t) = Title -> CiteField
P.Title (Title -> CiteField) -> Title -> CiteField
forall a b. (a -> b) -> a -> b
$ [Char] -> Title
P.S [Char]
t
layField (Type [Char]
t) = Title -> CiteField
P.Type (Title -> CiteField) -> Title -> CiteField
forall a b. (a -> b) -> a -> b
$ [Char] -> Title
P.S [Char]
t
layField (Volume Int
v) = Int -> CiteField
P.Volume Int
v
layField (Year Int
y) = Int -> CiteField
P.Year Int
y
layField (HowPublished (URL [Char]
u)) = HP -> CiteField
P.HowPublished (Title -> HP
P.URL (Title -> HP) -> Title -> HP
forall a b. (a -> b) -> a -> b
$ [Char] -> Title
P.S [Char]
u)
layField (HowPublished (Verb [Char]
v)) = HP -> CiteField
P.HowPublished (Title -> HP
P.Verb (Title -> HP) -> Title -> HP
forall a b. (a -> b) -> a -> b
$ [Char] -> Title
P.S [Char]
v)
makeL :: PrintingInformation -> ListType -> P.ListType
makeL :: PrintingInformation -> ListType -> ListType
makeL PrintingInformation
sm (Bullet [(ItemType, Maybe [Char])]
bs) = [(ItemType, Maybe Title)] -> ListType
P.Unordered ([(ItemType, Maybe Title)] -> ListType)
-> [(ItemType, Maybe Title)] -> ListType
forall a b. (a -> b) -> a -> b
$ ((ItemType, Maybe [Char]) -> (ItemType, Maybe Title))
-> [(ItemType, Maybe [Char])] -> [(ItemType, Maybe Title)]
forall a b. (a -> b) -> [a] -> [b]
map ((ItemType -> ItemType)
-> (Maybe [Char] -> Maybe Title)
-> (ItemType, Maybe [Char])
-> (ItemType, Maybe Title)
forall a b c d. (a -> b) -> (c -> d) -> (a, c) -> (b, d)
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap (PrintingInformation -> ItemType -> ItemType
item PrintingInformation
sm) (([Char] -> Title) -> Maybe [Char] -> Maybe Title
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Char] -> Title
P.S)) [(ItemType, Maybe [Char])]
bs
makeL PrintingInformation
sm (Numeric [(ItemType, Maybe [Char])]
ns) = [(ItemType, Maybe Title)] -> ListType
P.Ordered ([(ItemType, Maybe Title)] -> ListType)
-> [(ItemType, Maybe Title)] -> ListType
forall a b. (a -> b) -> a -> b
$ ((ItemType, Maybe [Char]) -> (ItemType, Maybe Title))
-> [(ItemType, Maybe [Char])] -> [(ItemType, Maybe Title)]
forall a b. (a -> b) -> [a] -> [b]
map ((ItemType -> ItemType)
-> (Maybe [Char] -> Maybe Title)
-> (ItemType, Maybe [Char])
-> (ItemType, Maybe Title)
forall a b c d. (a -> b) -> (c -> d) -> (a, c) -> (b, d)
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap (PrintingInformation -> ItemType -> ItemType
item PrintingInformation
sm) (([Char] -> Title) -> Maybe [Char] -> Maybe Title
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Char] -> Title
P.S)) [(ItemType, Maybe [Char])]
ns
makeL PrintingInformation
sm (Simple [ListTuple]
ps) = [(Title, ItemType, Maybe Title)] -> ListType
P.Simple ([(Title, ItemType, Maybe Title)] -> ListType)
-> [(Title, ItemType, Maybe Title)] -> ListType
forall a b. (a -> b) -> a -> b
$ (ListTuple -> (Title, ItemType, Maybe Title))
-> [ListTuple] -> [(Title, ItemType, Maybe Title)]
forall a b. (a -> b) -> [a] -> [b]
map (\(Title
x,ItemType
y,Maybe [Char]
z) -> (PrintingInformation -> Title -> Title
spec PrintingInformation
sm Title
x, PrintingInformation -> ItemType -> ItemType
item PrintingInformation
sm ItemType
y, ([Char] -> Title) -> Maybe [Char] -> Maybe Title
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Char] -> Title
P.S Maybe [Char]
z)) [ListTuple]
ps
makeL PrintingInformation
sm (Desc [ListTuple]
ps) = [(Title, ItemType, Maybe Title)] -> ListType
P.Desc ([(Title, ItemType, Maybe Title)] -> ListType)
-> [(Title, ItemType, Maybe Title)] -> ListType
forall a b. (a -> b) -> a -> b
$ (ListTuple -> (Title, ItemType, Maybe Title))
-> [ListTuple] -> [(Title, ItemType, Maybe Title)]
forall a b. (a -> b) -> [a] -> [b]
map (\(Title
x,ItemType
y,Maybe [Char]
z) -> (PrintingInformation -> Title -> Title
spec PrintingInformation
sm Title
x, PrintingInformation -> ItemType -> ItemType
item PrintingInformation
sm ItemType
y, ([Char] -> Title) -> Maybe [Char] -> Maybe Title
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Char] -> Title
P.S Maybe [Char]
z)) [ListTuple]
ps
makeL PrintingInformation
sm (Definitions [ListTuple]
ps) = [(Title, ItemType, Maybe Title)] -> ListType
P.Definitions ([(Title, ItemType, Maybe Title)] -> ListType)
-> [(Title, ItemType, Maybe Title)] -> ListType
forall a b. (a -> b) -> a -> b
$ (ListTuple -> (Title, ItemType, Maybe Title))
-> [ListTuple] -> [(Title, ItemType, Maybe Title)]
forall a b. (a -> b) -> [a] -> [b]
map (\(Title
x,ItemType
y,Maybe [Char]
z) -> (PrintingInformation -> Title -> Title
spec PrintingInformation
sm Title
x, PrintingInformation -> ItemType -> ItemType
item PrintingInformation
sm ItemType
y, ([Char] -> Title) -> Maybe [Char] -> Maybe Title
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Char] -> Title
P.S Maybe [Char]
z)) [ListTuple]
ps
item :: PrintingInformation -> ItemType -> P.ItemType
item :: PrintingInformation -> ItemType -> ItemType
item PrintingInformation
sm (Flat Title
i) = Title -> ItemType
P.Flat (Title -> ItemType) -> Title -> ItemType
forall a b. (a -> b) -> a -> b
$ PrintingInformation -> Title -> Title
spec PrintingInformation
sm Title
i
item PrintingInformation
sm (Nested Title
t ListType
s) = Title -> ListType -> ItemType
P.Nested (PrintingInformation -> Title -> Title
spec PrintingInformation
sm Title
t) (PrintingInformation -> ListType -> ListType
makeL PrintingInformation
sm ListType
s)