module Language.Drasil.Printing.Import.Document where
import Language.Drasil hiding (neg, sec, symbol, isIn)
import Language.Drasil.Development (showUID)
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.Sentence (spec)
import Control.Lens ((^.))
import Data.Bifunctor (bimap, second)
makeDocument :: PrintingInformation -> Document -> T.Document
makeDocument :: PrintingInformation -> Document -> Document
makeDocument sm :: PrintingInformation
sm (Document titleLb :: Title
titleLb authorName :: Title
authorName _ sections :: [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 sm :: PrintingInformation
sm (Notebook titleLb :: Title
titleLb authorName :: Title
authorName sections :: [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)
createLayout :: PrintingInformation -> [Section] -> [T.LayoutObj]
createLayout :: PrintingInformation -> [Section] -> [LayoutObj]
createLayout sm :: PrintingInformation
sm = (Section -> LayoutObj) -> [Section] -> [LayoutObj]
forall a b. (a -> b) -> [a] -> [b]
map (PrintingInformation -> Int -> Section -> LayoutObj
sec PrintingInformation
sm 0)
createLayout' :: PrintingInformation -> [Section] -> [T.LayoutObj]
createLayout' :: PrintingInformation -> [Section] -> [LayoutObj]
createLayout' sm :: PrintingInformation
sm = (Section -> LayoutObj) -> [Section] -> [LayoutObj]
forall a b. (a -> b) -> [a] -> [b]
map (PrintingInformation -> Int -> Section -> LayoutObj
cel PrintingInformation
sm 0)
sec :: PrintingInformation -> Int -> Section -> T.LayoutObj
sec :: PrintingInformation -> Int -> Section -> LayoutObj
sec sm :: PrintingInformation
sm depth :: Int
depth x :: Section
x@(Section titleLb :: Title
titleLb contents :: [SecCons]
contents _) =
let refr :: Title
refr = String -> Title
P.S (Section -> String
forall s. Referable s => s -> String
refAdd Section
x) in
Tags -> [LayoutObj] -> Title -> LayoutObj
T.HDiv [Tags -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat (Int -> String -> Tags
forall a. Int -> a -> [a]
replicate Int
depth "sub") String -> String -> String
forall a. [a] -> [a] -> [a]
++ "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 sm :: PrintingInformation
sm depth :: Int
depth x :: Section
x@(Section titleLb :: Title
titleLb contents :: [SecCons]
contents _) =
let refr :: Title
refr = String -> Title
P.S (Section -> String
forall s. Referable s => s -> String
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 sm :: PrintingInformation
sm currDepth :: Int
currDepth (Sub s :: Section
s) = PrintingInformation -> Int -> Section -> LayoutObj
sec PrintingInformation
sm (Int
currDepthInt -> Int -> Int
forall a. Num a => a -> a -> a
+1) Section
s
layout sm :: PrintingInformation
sm _ (Con c :: Contents
c) = PrintingInformation -> Contents -> LayoutObj
lay PrintingInformation
sm Contents
c
lay :: PrintingInformation -> Contents -> T.LayoutObj
lay :: PrintingInformation -> Contents -> LayoutObj
lay sm :: PrintingInformation
sm (LlC x :: LabelledContent
x) = PrintingInformation -> LabelledContent -> LayoutObj
layLabelled PrintingInformation
sm LabelledContent
x
lay sm :: PrintingInformation
sm (UlC x :: 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
accessContents)
layLabelled :: PrintingInformation -> LabelledContent -> T.LayoutObj
layLabelled :: PrintingInformation -> LabelledContent -> LayoutObj
layLabelled sm :: PrintingInformation
sm x :: LabelledContent
x@(LblC _ (Table hdr :: [Title]
hdr lls :: [[Title]]
lls t :: Title
t b :: Bool
b)) = Tags -> [[Title]] -> Title -> Bool -> Title -> LayoutObj
T.Table ["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)
(String -> Title
P.S (String -> Title) -> String -> Title
forall a b. (a -> b) -> a -> b
$ LblType -> String
getAdd (LblType -> String) -> LblType -> String
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 sm :: PrintingInformation
sm x :: LabelledContent
x@(LblC _ (EqnBlock c :: ModelExpr
c)) = Tags -> [LayoutObj] -> Title -> LayoutObj
T.HDiv ["equation"]
[Title -> LayoutObj
T.EqnBlock (Expr -> Title
P.E (ModelExpr -> PrintingInformation -> Expr
modelExpr ModelExpr
c PrintingInformation
sm))]
(String -> Title
P.S (String -> Title) -> String -> Title
forall a b. (a -> b) -> a -> b
$ LblType -> String
getAdd (LblType -> String) -> LblType -> String
forall a b. (a -> b) -> a -> b
$ LabelledContent -> LblType
forall b. HasRefAddress b => b -> LblType
getRefAdd LabelledContent
x)
layLabelled sm :: PrintingInformation
sm x :: LabelledContent
x@(LblC _ (Figure c :: Title
c f :: String
f wp :: MaxWidthPercent
wp)) = Title -> Title -> String -> MaxWidthPercent -> LayoutObj
T.Figure
(String -> Title
P.S (String -> Title) -> String -> Title
forall a b. (a -> b) -> a -> b
$ LblType -> String
getAdd (LblType -> String) -> LblType -> String
forall a b. (a -> b) -> a -> b
$ LabelledContent -> LblType
forall b. HasRefAddress b => b -> LblType
getRefAdd LabelledContent
x)
(PrintingInformation -> Title -> Title
spec PrintingInformation
sm Title
c) String
f MaxWidthPercent
wp
layLabelled sm :: PrintingInformation
sm x :: LabelledContent
x@(LblC _ (Graph ps :: [(Title, Title)]
ps w :: Maybe MaxWidthPercent
w h :: Maybe MaxWidthPercent
h t :: 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 (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)
(String -> Title
P.S (String -> Title) -> String -> Title
forall a b. (a -> b) -> a -> b
$ LblType -> String
getAdd (LblType -> String) -> LblType -> String
forall a b. (a -> b) -> a -> b
$ LabelledContent -> LblType
forall b. HasRefAddress b => b -> LblType
getRefAdd LabelledContent
x)
layLabelled sm :: PrintingInformation
sm x :: LabelledContent
x@(LblC _ (Defini dtyp :: DType
dtyp pairs :: [(String, [Contents])]
pairs)) = DType -> [(String, [LayoutObj])] -> Title -> LayoutObj
T.Definition
DType
dtyp ([(String, [Contents])] -> [(String, [LayoutObj])]
forall a. [(a, [Contents])] -> [(a, [LayoutObj])]
layPairs [(String, [Contents])]
pairs)
(String -> Title
P.S (String -> Title) -> String -> Title
forall a b. (a -> b) -> a -> b
$ LblType -> String
getAdd (LblType -> String) -> LblType -> String
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 (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 sm :: PrintingInformation
sm (LblC _ (Paragraph c :: Title
c)) = Title -> LayoutObj
T.Paragraph (PrintingInformation -> Title -> Title
spec PrintingInformation
sm Title
c)
layLabelled sm :: PrintingInformation
sm x :: LabelledContent
x@(LblC _ (DerivBlock h :: Title
h d :: [RawContent]
d)) = Tags -> [LayoutObj] -> Title -> LayoutObj
T.HDiv ["subsubsubsection"]
(Int -> Title -> Title -> LayoutObj
T.Header 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 = String -> Title
P.S (String -> Title) -> String -> Title
forall a b. (a -> b) -> a -> b
$ LabelledContent -> String
forall s. Referable s => s -> String
refAdd LabelledContent
x String -> String -> String
forall a. [a] -> [a] -> [a]
++ "Deriv"
layLabelled sm :: PrintingInformation
sm (LblC _ (Enumeration cs :: 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 _ (LblC _ (Bib 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 -> RawContent -> T.LayoutObj
layUnlabelled :: PrintingInformation -> RawContent -> LayoutObj
layUnlabelled sm :: PrintingInformation
sm (Table hdr :: [Title]
hdr lls :: [[Title]]
lls t :: Title
t b :: Bool
b) = Tags -> [[Title]] -> Title -> Bool -> Title -> LayoutObj
T.Table ["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) (String -> Title
P.S "nolabel0") Bool
b (PrintingInformation -> Title -> Title
spec PrintingInformation
sm Title
t)
layUnlabelled sm :: PrintingInformation
sm (Paragraph c :: Title
c) = Title -> LayoutObj
T.Paragraph (PrintingInformation -> Title -> Title
spec PrintingInformation
sm Title
c)
layUnlabelled sm :: PrintingInformation
sm (EqnBlock c :: ModelExpr
c) = Tags -> [LayoutObj] -> Title -> LayoutObj
T.HDiv ["equation"] [Title -> LayoutObj
T.EqnBlock (Expr -> Title
P.E (ModelExpr -> PrintingInformation -> Expr
modelExpr ModelExpr
c PrintingInformation
sm))] Title
P.EmptyS
layUnlabelled sm :: PrintingInformation
sm (DerivBlock h :: Title
h d :: [RawContent]
d) = Tags -> [LayoutObj] -> Title -> LayoutObj
T.HDiv ["subsubsubsection"]
(Int -> Title -> Title -> LayoutObj
T.Header 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 = String -> Title
P.S "nolabel1"
layUnlabelled sm :: PrintingInformation
sm (Enumeration cs :: 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 sm :: PrintingInformation
sm (Figure c :: Title
c f :: String
f wp :: MaxWidthPercent
wp) = Title -> Title -> String -> MaxWidthPercent -> LayoutObj
T.Figure (String -> Title
P.S "nolabel2") (PrintingInformation -> Title -> Title
spec PrintingInformation
sm Title
c) String
f MaxWidthPercent
wp
layUnlabelled sm :: PrintingInformation
sm (Graph ps :: [(Title, Title)]
ps w :: Maybe MaxWidthPercent
w h :: Maybe MaxWidthPercent
h t :: 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 (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) (String -> Title
P.S "nolabel6")
layUnlabelled sm :: PrintingInformation
sm (Defini dtyp :: DType
dtyp pairs :: [(String, [Contents])]
pairs) = DType -> [(String, [LayoutObj])] -> Title -> LayoutObj
T.Definition DType
dtyp ([(String, [Contents])] -> [(String, [LayoutObj])]
forall a. [(a, [Contents])] -> [(a, [LayoutObj])]
layPairs [(String, [Contents])]
pairs) (String -> Title
P.S "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 (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 y :: 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
accessContents)
layUnlabelled _ (Bib 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
layCite :: Citation -> P.Citation
layCite :: Citation -> Citation
layCite c :: Citation
c = String -> CitationKind -> [CiteField] -> Citation
P.Cite (Citation -> String
forall a. HasUID a => a -> String
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]
getFields))
layField :: CiteField -> P.CiteField
layField :: CiteField -> CiteField
layField (Address s :: String
s) = Title -> CiteField
P.Address (Title -> CiteField) -> Title -> CiteField
forall a b. (a -> b) -> a -> b
$ String -> Title
P.S String
s
layField (Author p :: People
p) = People -> CiteField
P.Author People
p
layField (BookTitle b :: String
b) = Title -> CiteField
P.BookTitle (Title -> CiteField) -> Title -> CiteField
forall a b. (a -> b) -> a -> b
$ String -> Title
P.S String
b
layField (Chapter c :: Int
c) = Int -> CiteField
P.Chapter Int
c
layField (Edition e :: Int
e) = Int -> CiteField
P.Edition Int
e
layField (Editor e :: People
e) = People -> CiteField
P.Editor People
e
layField (Institution i :: String
i) = Title -> CiteField
P.Institution (Title -> CiteField) -> Title -> CiteField
forall a b. (a -> b) -> a -> b
$ String -> Title
P.S String
i
layField (Journal j :: String
j) = Title -> CiteField
P.Journal (Title -> CiteField) -> Title -> CiteField
forall a b. (a -> b) -> a -> b
$ String -> Title
P.S String
j
layField (Month m :: Month
m) = Month -> CiteField
P.Month Month
m
layField (Note n :: String
n) = Title -> CiteField
P.Note (Title -> CiteField) -> Title -> CiteField
forall a b. (a -> b) -> a -> b
$ String -> Title
P.S String
n
layField (Number n :: Int
n) = Int -> CiteField
P.Number Int
n
layField (Organization o :: String
o) = Title -> CiteField
P.Organization (Title -> CiteField) -> Title -> CiteField
forall a b. (a -> b) -> a -> b
$ String -> Title
P.S String
o
layField (Pages p :: [Int]
p) = [Int] -> CiteField
P.Pages [Int]
p
layField (Publisher p :: String
p) = Title -> CiteField
P.Publisher (Title -> CiteField) -> Title -> CiteField
forall a b. (a -> b) -> a -> b
$ String -> Title
P.S String
p
layField (School s :: String
s) = Title -> CiteField
P.School (Title -> CiteField) -> Title -> CiteField
forall a b. (a -> b) -> a -> b
$ String -> Title
P.S String
s
layField (Series s :: String
s) = Title -> CiteField
P.Series (Title -> CiteField) -> Title -> CiteField
forall a b. (a -> b) -> a -> b
$ String -> Title
P.S String
s
layField (Title t :: String
t) = Title -> CiteField
P.Title (Title -> CiteField) -> Title -> CiteField
forall a b. (a -> b) -> a -> b
$ String -> Title
P.S String
t
layField (Type t :: String
t) = Title -> CiteField
P.Type (Title -> CiteField) -> Title -> CiteField
forall a b. (a -> b) -> a -> b
$ String -> Title
P.S String
t
layField (Volume v :: Int
v) = Int -> CiteField
P.Volume Int
v
layField (Year y :: Int
y) = Int -> CiteField
P.Year Int
y
layField (HowPublished (URL u :: String
u)) = HP -> CiteField
P.HowPublished (Title -> HP
P.URL (Title -> HP) -> Title -> HP
forall a b. (a -> b) -> a -> b
$ String -> Title
P.S String
u)
layField (HowPublished (Verb v :: String
v)) = HP -> CiteField
P.HowPublished (Title -> HP
P.Verb (Title -> HP) -> Title -> HP
forall a b. (a -> b) -> a -> b
$ String -> Title
P.S String
v)
makeL :: PrintingInformation -> ListType -> P.ListType
makeL :: PrintingInformation -> ListType -> ListType
makeL sm :: PrintingInformation
sm (Bullet bs :: [(ItemType, Maybe String)]
bs) = [(ItemType, Maybe Title)] -> ListType
P.Unordered ([(ItemType, Maybe Title)] -> ListType)
-> [(ItemType, Maybe Title)] -> ListType
forall a b. (a -> b) -> a -> b
$ ((ItemType, Maybe String) -> (ItemType, Maybe Title))
-> [(ItemType, Maybe String)] -> [(ItemType, Maybe Title)]
forall a b. (a -> b) -> [a] -> [b]
map ((ItemType -> ItemType)
-> (Maybe String -> Maybe Title)
-> (ItemType, Maybe String)
-> (ItemType, Maybe Title)
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) ((String -> Title) -> Maybe String -> Maybe Title
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Title
P.S)) [(ItemType, Maybe String)]
bs
makeL sm :: PrintingInformation
sm (Numeric ns :: [(ItemType, Maybe String)]
ns) = [(ItemType, Maybe Title)] -> ListType
P.Ordered ([(ItemType, Maybe Title)] -> ListType)
-> [(ItemType, Maybe Title)] -> ListType
forall a b. (a -> b) -> a -> b
$ ((ItemType, Maybe String) -> (ItemType, Maybe Title))
-> [(ItemType, Maybe String)] -> [(ItemType, Maybe Title)]
forall a b. (a -> b) -> [a] -> [b]
map ((ItemType -> ItemType)
-> (Maybe String -> Maybe Title)
-> (ItemType, Maybe String)
-> (ItemType, Maybe Title)
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) ((String -> Title) -> Maybe String -> Maybe Title
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Title
P.S)) [(ItemType, Maybe String)]
ns
makeL sm :: PrintingInformation
sm (Simple ps :: [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 (\(x :: Title
x,y :: ItemType
y,z :: Maybe String
z) -> (PrintingInformation -> Title -> Title
spec PrintingInformation
sm Title
x, PrintingInformation -> ItemType -> ItemType
item PrintingInformation
sm ItemType
y, (String -> Title) -> Maybe String -> Maybe Title
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Title
P.S Maybe String
z)) [ListTuple]
ps
makeL sm :: PrintingInformation
sm (Desc ps :: [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 (\(x :: Title
x,y :: ItemType
y,z :: Maybe String
z) -> (PrintingInformation -> Title -> Title
spec PrintingInformation
sm Title
x, PrintingInformation -> ItemType -> ItemType
item PrintingInformation
sm ItemType
y, (String -> Title) -> Maybe String -> Maybe Title
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Title
P.S Maybe String
z)) [ListTuple]
ps
makeL sm :: PrintingInformation
sm (Definitions ps :: [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 (\(x :: Title
x,y :: ItemType
y,z :: Maybe String
z) -> (PrintingInformation -> Title -> Title
spec PrintingInformation
sm Title
x, PrintingInformation -> ItemType -> ItemType
item PrintingInformation
sm ItemType
y, (String -> Title) -> Maybe String -> Maybe Title
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Title
P.S Maybe String
z)) [ListTuple]
ps
item :: PrintingInformation -> ItemType -> P.ItemType
item :: PrintingInformation -> ItemType -> ItemType
item sm :: PrintingInformation
sm (Flat i :: 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 sm :: PrintingInformation
sm (Nested t :: Title
t s :: ListType
s) = Title -> ListType -> ItemType
P.Nested (PrintingInformation -> Title -> Title
spec PrintingInformation
sm Title
t) (PrintingInformation -> ListType -> ListType
makeL PrintingInformation
sm ListType
s)