-- | Here, principal LaTeX /commands/ and /environments/. module Text.LaTeX.Commands ( -- * Document's Properties documentclass , usepackage , pagestyle , thispagestyle , author , title -- * Document Environment , document -- * Text order , pfbk , lnbk , lnbk_ , newpage , linebreak , nolinebreak , pagebreak , nopagebreak , fussy , sloppy , endsen , frenchspacing , par -- * Importing , include , includeonly , input -- * Hyphenation , hyphenation , hyp -- * Pre-made , today , tex , latex , latexe -- * Sections , section , section_ , sectiontab , subsection , subsection_ , subsectiontab , subsubsection , subsubsection_ , subsubsectiontab , paragraph , paragraph_ , paragraphtab , subparagraph , subparagraph_ , subparagraphtab , part , part_ , parttab , chapter , chapter_ , chaptertab , appendix , maketitle , tableofcontents , frontmatter , mainmatter , backmatter -- * Cross references , label , ref , pageref -- * Footnotes , footnote -- * Emphasized , underline , emph -- * Environments , itemize , enumerate , description , item , flushleft , flushright , center , quote , quotation , verse , abstract , verbatim , verbatim_ , verb , verb_ -- * Floating Bodies , figure , table , caption , listoffigures , listoftables , clearpage , cleardoublepage -- * Customizing , newcommand , renewcommand , providecommand , newenvironment , ignorespaces , ignorespacesafterend , providesPackage -- * Fonts -- $fontslabel -- ** Format , textrm , texttt , textmd , textup , textsl , textsf , textbf , textit , textsc , textnormal -- ** Size , tiny , scriptsize , footnotesize , small , normalsize , large , large2 , large3 , huge , huge2 -- * Spacing , linespread , hspace , hspace_ , vspace , vspace_ , stretch , skip , bigskip , smallskip -- * Boxes , mbox , mbox_ , fbox , parbox , minipage , makebox , framebox , raisebox -- * Tabular , Tabular , cjustified , csep , tabular , (&) , (//) , hline , cline , multicolumn , LxMatrix , matrixTab -- * Others , protect , phantom ) where import Data.List import Text.LaTeX.Monad import Text.LaTeX.Define import Text.LaTeX.Arguments import Text.LaTeX.Packages import Text.LaTeX.Result -- Special Characters char :: Char -> LaTeX char = chReplace resCharsStr where chReplace [] c = lx $ toResult [c] chReplace ((x,y):xs) c = if x == c then lx y else chReplace xs c string :: String -> LaTeX string = mapM_ char qts :: LaTeX -> LaTeX qts x = do "``" x "''" ldots :: LaTeX ldots = comm0 "ldots" -- documentclass :: [ClassOption] -> Class -> LaTeX documentclass = comm4 "documentclass" usepackage :: [PackageOption] -> Package -> LaTeX usepackage = comm4 "usepackage" pagestyle :: Style -> LaTeX pagestyle = comm1 "pagestyle" -- | A local version of 'pagestyle'. thispagestyle :: Style -> LaTeX thispagestyle = comm1 "thispagestyle" author :: Name -> LaTeX author = comm1 "author" title :: Title -> LaTeX title = comm1 "title" date :: Date -> LaTeX date = comm1 "date" document :: LaTeX -> LaTeX document = env "document" -- Text Order pfbk :: LaTeX pfbk = "\n\n" lnbk :: LaTeX lnbk = comm0_ "\\" lnbk_ :: LaTeX lnbk_ = comm0_ "\\*" newpage :: LaTeX newpage = comm0 "newpage" linebreak :: Int -> LaTeX linebreak = comm3 "linebreak" . (:[]) . lxany nolinebreak :: Int -> LaTeX nolinebreak = comm3 "nolinebreak" . (:[]) . lxany pagebreak :: Int -> LaTeX pagebreak = comm3 "pagebreak" . (:[]) . lxany nopagebreak :: Int -> LaTeX nopagebreak = comm3 "nopagebreak" . (:[]) . lxany fussy :: LaTeX fussy = comm0 "fussy" sloppy :: LaTeX sloppy = comm0 "sloppy" endsen :: LaTeX endsen = comm0_ "@" frenchspacing :: LaTeX frenchspacing = comm0 "frenchspacing" -- Importing include :: FilePath -> LaTeX include = comm1 "include" . lx . toResult includeonly :: [FilePath] -> LaTeX includeonly = comm1 "includeonly" . mapM_ (lx . toResult) . intersperse "," input :: FilePath -> LaTeX input = comm1 "input" . lx . toResult -- Hyphenation hyphenation :: [Word] -> LaTeX hyphenation = comm1 "hyphenation" . lx . toResult . unwords hyp :: LaTeX hyp = comm0 "-" -- Ready-Made Strings today :: LaTeX today = comm0 "today" tex :: LaTeX tex = comm0 "TeX" latex :: LaTeX latex = comm0 "LaTeX" latexe :: LaTeX latexe = comm0 "LaTeXe" -- Sections (Article) section :: Title -> LaTeX section = comm1 "section" section_ :: Title -> LaTeX section_ = comm1 "section*" sectiontab :: Title -> Title -> LaTeX sectiontab t1 = comm4 "section" [t1] subsection :: Title -> LaTeX subsection = comm1 "subsection" subsection_ :: Title -> LaTeX subsection_ = comm1 "subsection*" subsectiontab :: Title -> Title -> LaTeX subsectiontab t1 = comm4 "subsection" [t1] subsubsection :: Title -> LaTeX subsubsection = comm1 "subsubsection" subsubsection_ :: Title -> LaTeX subsubsection_ = comm1 "subsubsection*" subsubsectiontab :: Title -> Title -> LaTeX subsubsectiontab t1 = comm4 "subsubsection" [t1] paragraph :: Title -> LaTeX paragraph = comm1 "paragraph" paragraph_ :: Title -> LaTeX paragraph_ = comm1 "paragraph*" paragraphtab :: Title -> Title -> LaTeX paragraphtab t1 = comm4 "paragraph" [t1] subparagraph :: Title -> LaTeX subparagraph = comm1 "subparagraph" subparagraph_ :: Title -> LaTeX subparagraph_ = comm1 "subparagraph*" subparagraphtab :: Title -> Title -> LaTeX subparagraphtab t1 = comm4 "subparagraph" [t1] part :: Title -> LaTeX part = comm1 "part" part_ :: Title -> LaTeX part_ = comm1 "part*" parttab :: Title -> Title -> LaTeX parttab t1 = comm4 "part" [t1] -- Sections (Report or Book) chapter :: Title -> LaTeX chapter = comm1 "chapter" chapter_ :: Title -> LaTeX chapter_ = comm1 "chapter*" chaptertab :: Title -> Title -> LaTeX chaptertab t1 = comm4 "chapter" [t1] -- Sections (Others) appendix :: LaTeX appendix = comm0 "appendix" maketitle :: LaTeX maketitle = comm0 "maketitle" tableofcontents :: LaTeX tableofcontents = comm0 "tableofcontents" -- For Book Class frontmatter :: LaTeX frontmatter = comm0 "frontmatter" mainmatter :: LaTeX mainmatter = comm0 "mainmatter" backmatter :: LaTeX backmatter = comm0 "backmatter" -- Cross References label :: Marker -> LaTeX label = comm1 "label" ref :: Marker -> LaTeX ref = comm1 "ref" pageref :: Marker -> LaTeX pageref = comm1 "pageref" -- Footnotes footnote :: Text -> LaTeX footnote = comm1 "footnote" -- Emphasized underline :: Text -> LaTeX underline = comm1 "underline" emph :: Text -> LaTeX emph = comm1 "emph" -- Environments itemize :: LaTeX -> LaTeX itemize = env "itemize" enumerate :: LaTeX -> LaTeX enumerate = env "enumerate" description :: LaTeX -> LaTeX description = env "description" item :: [ItemOption] -> LaTeX item = comm3 "item" flushleft :: LaTeX -> LaTeX flushleft = env "flushleft" flushright :: LaTeX -> LaTeX flushright = env "flushright" center :: LaTeX -> LaTeX center = env "center" quote :: LaTeX -> LaTeX quote = env "quote" quotation :: LaTeX -> LaTeX quotation = env "quotation" verse :: LaTeX -> LaTeX verse = env "verse" abstract :: LaTeX -> LaTeX abstract = env "abstract" verbatim :: LaTeX -> LaTeX verbatim = env "verbatim" verbatim_ :: LaTeX -> LaTeX verbatim_ = env "verbatim*" verb :: LaTeX -> LaTeX verb = (comm0_ "verb" >>) . reslx sep verb_ :: LaTeX -> LaTeX verb_ = (comm0_ "verb*" >>) . reslx sep -- Floating Bodies figure :: [PlacementSpecifier] -> LaTeX -> LaTeX figure = env2 "figure" table :: [PlacementSpecifier] -> LaTeX -> LaTeX table = env2 "table" caption :: Text -> LaTeX caption = comm1 "caption" listoffigures :: LaTeX listoffigures = comm0 "listoffigures" listoftables :: LaTeX listoftables = comm0 "listoftables" clearpage :: LaTeX clearpage = comm0 "clearpage" cleardoublepage :: LaTeX cleardoublepage = "cleardoblepage" -- Customizing newcommand :: Name -> [Int] -> LaTeX -> LaTeX newcommand n i = comm6 "newcommand" n (map lxany i) renewcommand :: Name -> [Int] -> LaTeX -> LaTeX renewcommand n i = comm6 "renewcommand" n (map lxany i) providecommand :: Name -> [Int] -> LaTeX -> LaTeX providecommand n i = comm6 "providecommand" n (map lxany i) newenvironment :: Name -> [Int] -> LaTeX -> LaTeX -> LaTeX newenvironment n i = comm7 "newenvironment" n (map lxany i) ignorespaces :: LaTeX ignorespaces = comm0 "ignorespaces" ignorespacesafterend :: LaTeX ignorespacesafterend = comm0 "ignorespacesafterend" providesPackage :: Name -> LaTeX providesPackage = comm1 "ProvidesPackage" -- Fonts -- $fontslabel -- #Fonts# -- | Roman font textrm :: LaTeX -> LaTeX textrm = comm1 "textrm" -- | Monospaced font texttt :: LaTeX -> LaTeX texttt = comm1 "texttt" -- | Medium font textmd :: LaTeX -> LaTeX textmd = comm1 "textmd" -- | Upright font textup :: LaTeX -> LaTeX textup = comm1 "textup" -- | Slanted font textsl :: LaTeX -> LaTeX textsl = comm1 "textsl" -- | Sans Serif font textsf :: LaTeX -> LaTeX textsf = comm1 "textsf" -- | Bold font textbf :: LaTeX -> LaTeX textbf = comm1 "textbf" -- | Italic font textit :: LaTeX -> LaTeX textit = comm1 "textit" -- | Small Caps font textsc :: LaTeX -> LaTeX textsc = comm1 "textsc" -- | Default font textnormal :: LaTeX -> LaTeX textnormal = comm1 "textnormal" -- Font Sizes tiny :: LaTeX -> LaTeX tiny = comm8 "tinty" scriptsize :: LaTeX -> LaTeX scriptsize = comm8 "scriptsize" footnotesize :: LaTeX -> LaTeX footnotesize = comm8 "footnotesize" small :: LaTeX -> LaTeX small = comm8 "small" normalsize :: LaTeX -> LaTeX normalsize = comm8 "normalsize" large :: LaTeX -> LaTeX large = comm8 "large" large2 :: LaTeX -> LaTeX large2 = comm8 "Large" large3 :: LaTeX -> LaTeX large3 = comm8 "LARGE" huge :: LaTeX -> LaTeX huge = comm8 "huge" huge2 :: LaTeX -> LaTeX huge2 = comm8 "Huge" -- par :: LaTeX par = comm0 "par" -- Spacing linespread :: Float -> LaTeX linespread = comm1 "linespread" . lxany hspace :: LaTeX -> LaTeX hspace = comm1 "hspace" hspace_ :: LaTeX -> LaTeX hspace_ = comm1 "hspace*" vspace :: LaTeX -> LaTeX vspace = comm1 "vspace" vspace_ :: LaTeX -> LaTeX vspace_ = comm1 "vspace*" stretch :: Int -> LaTeX stretch = comm1 "stretch" . lxany skip :: Float -> LaTeX skip x = do lnbk lx . bs . toResult $ show x bigskip :: LaTeX bigskip = comm0 "bigskip" smallskip :: LaTeX smallskip = comm0 "smallskip" -- Boxes mbox :: LaTeX -> LaTeX mbox = comm1 "mbox" mbox_ :: LaTeX mbox_ = mbox "" fbox :: LaTeX -> LaTeX fbox = comm1 "fbox" parbox :: [Char] -> Width -> LaTeX -> LaTeX parbox c = comm9 "parbox" (if null c then [] else [lx $ toResult c]) minipage :: [Char] -> Width -> LaTeX -> LaTeX minipage c = env3 "minipage" (if null c then [] else [lx $ toResult c]) makebox :: [Width] -> [Char] -> LaTeX -> LaTeX makebox w c = comm10 "makebox" w (if null c then [] else [lx $ toResult c]) framebox :: [Width] -> [Char] -> LaTeX -> LaTeX framebox w c = comm10 "framebox" w (if null c then [] else [lx $ toResult c]) raisebox :: Lift -> [Extend] -> [Extend] -> LaTeX -> LaTeX raisebox = comm11 "raisebox" -- Others protect :: LaTeX protect = comm0_ "protect" phantom :: LaTeX -> LaTeX phantom = comm1 "phantom" -- Tabular type Tabular = LaTeX cjustified :: Width -> LaTeX cjustified = ("p">>) . keys csep :: LaTeX -> LaTeX csep = ("@">>) . keys tabular :: [LaTeX] -> LaTeX -> LaTeX -> Tabular tabular = env3 "tabular" (&) :: LaTeX -> LaTeX -> LaTeX x & y = do x ; " & " ; y (//) :: LaTeX -> LaTeX -> LaTeX x // y = do x lnbk ; "\n" y hline :: LaTeX hline = comm0 "hline" cline :: Int -> Int -> LaTeX cline n m = comm1 "cline" $ lxany n - lxany m multicolumn :: Int -> LaTeX -> LaTeX -> LaTeX multicolumn n = comm12 "multicolumn" $ lxany n type LxMatrix = [[LaTeX]] matrixTab :: [LaTeX] -> LaTeX -> LxMatrix -> Tabular matrixTab p spec = tabular p spec . foldr1 (//) . map (foldr1 (&)) -- CAUTION: Error with empty matrix!