{-# LANGUAGE OverloadedStrings #-} -- | Here, principal LaTeX m /commands/ and /environments/. module Text.LaTeX.Commands ( -- * Document's Properties documentclass , usepackage , pagestyle , thispagestyle , author , title -- * Document Environment , document -- * Text Layout , lnbk , lnbk_ , pfbk , 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 -- $fontsize , 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 , string , qts , ldots ) where import Prelude hiding (unwords) import Data.List (intersperse) import GHC.Exts (fromString) import Data.Monoid (mappend) import Data.String.Combinators (braces,unwords,between ,mid ,newline,brackets) import Text.LaTeX.Monad import Text.LaTeX.Define import Text.LaTeX.Arguments import Text.LaTeX.Packages import Text.LaTeX.Result -- Special Characters char :: Monad m => Char -> LaTeX m char = chReplace resCharsStr where chReplace [] c = lx $ toResult [c] chReplace ((x,y):xs) c = if x == c then lx y else chReplace xs c -- | Like 'fromString', but taking care with reserved characters. string :: Monad m => String -> LaTeX m string = mapM_ char -- | Delimite between quotes a text. qts :: Monad m => LaTeX m -> LaTeX m qts = between "``" "''" -- | Write a ellipsis. ldots :: Monad m => LaTeX m ldots = comm0 "ldots" -- -- | In header, determines the document class. documentclass :: Monad m => [ClassOption m] -> Class m -> LaTeX m documentclass = comm4 "documentclass" -- | In header, import a package. usepackage :: Monad m => [PackageOption m] -> Package m -> LaTeX m usepackage = comm4 "usepackage" -- | In header, determines page style. pagestyle :: Monad m => Style m -> LaTeX m pagestyle = comm1 "pagestyle" -- | A local version of 'pagestyle', to use for any page. thispagestyle :: Monad m => Style m -> LaTeX m thispagestyle = comm1 "thispagestyle" -- | In header, especifies the document's author. author :: Monad m => Name m -> LaTeX m author = comm1 "author" -- | In header, especifies the document's title. title :: Monad m => Title m -> LaTeX m title = comm1 "title" -- | In header, inserts a date of writing. -- If you don't specify one, it takes the date of export. date :: Monad m => Date m -> LaTeX m date = comm1 "date" -- Document environment document :: Monad m => LaTeX m -> LaTeX m document = env "document" -- Text m Order -- | Starts a new line. lnbk :: Monad m => LaTeX m lnbk = comm0_ "\\" -- | Starts a new paragraph. pfbk :: Monad m => LaTeX m pfbk = newline >> newline lnbk_ :: Monad m => LaTeX m lnbk_ = comm0_ "\\*" -- | Starts a new page. newpage :: Monad m => LaTeX m newpage = comm0 "newpage" linebreak :: Monad m => Int -> LaTeX m linebreak = comm3 "linebreak" . (:[]) . lxany nolinebreak :: Monad m => Int -> LaTeX m nolinebreak = comm3 "nolinebreak" . (:[]) . lxany pagebreak :: Monad m => Int -> LaTeX m pagebreak = comm3 "pagebreak" . (:[]) . lxany nopagebreak :: Monad m => Int -> LaTeX m nopagebreak = comm3 "nopagebreak" . (:[]) . lxany fussy :: Monad m => LaTeX m fussy = comm0 "fussy" sloppy :: Monad m => LaTeX m sloppy = comm0 "sloppy" endsen :: Monad m => LaTeX m endsen = comm0_ "@" frenchspacing :: Monad m => LaTeX m frenchspacing = comm0 "frenchspacing" -- Importing include :: Monad m => FilePath -> LaTeX m include = comm1 "include" . fromString includeonly :: Monad m => [FilePath] -> LaTeX m includeonly = comm1 "includeonly" . mapM_ fromString . intersperse "," input :: Monad m => FilePath -> LaTeX m input = comm1 "input" . fromString -- Hyphenation hyphenation :: Monad m => [Word m] -> LaTeX m hyphenation = comm1 "hyphenation" . unwords hyp :: Monad m => LaTeX m hyp = comm0 "-" -- Ready-Made Strings -- | Writes current date. today :: Monad m => LaTeX m today = comm0 "today" -- | TeX nice word. tex :: Monad m => LaTeX m tex = comm0 "TeX" -- | LaTeX m nice word. latex :: Monad m => LaTeX m latex = comm0 "LaTeX m" -- | LaTeX m2e nice word. latexe :: Monad m => LaTeX m latexe = comm0 "LaTeX me" -- Sections (Article) section :: Monad m => Title m -> LaTeX m section = comm1 "section" section_ :: Monad m => Title m -> LaTeX m section_ = comm1 "section*" sectiontab :: Monad m => Title m -> Title m -> LaTeX m sectiontab t1 = comm4 "section" [t1] subsection :: Monad m => Title m -> LaTeX m subsection = comm1 "subsection" subsection_ :: Monad m => Title m -> LaTeX m subsection_ = comm1 "subsection*" subsectiontab :: Monad m => Title m -> Title m -> LaTeX m subsectiontab t1 = comm4 "subsection" [t1] subsubsection :: Monad m => Title m -> LaTeX m subsubsection = comm1 "subsubsection" subsubsection_ :: Monad m => Title m -> LaTeX m subsubsection_ = comm1 "subsubsection*" subsubsectiontab :: Monad m => Title m -> Title m -> LaTeX m subsubsectiontab t1 = comm4 "subsubsection" [t1] paragraph :: Monad m => Title m -> LaTeX m paragraph = comm1 "paragraph" paragraph_ :: Monad m => Title m -> LaTeX m paragraph_ = comm1 "paragraph*" paragraphtab :: Monad m => Title m -> Title m -> LaTeX m paragraphtab t1 = comm4 "paragraph" [t1] subparagraph :: Monad m => Title m -> LaTeX m subparagraph = comm1 "subparagraph" subparagraph_ :: Monad m => Title m -> LaTeX m subparagraph_ = comm1 "subparagraph*" subparagraphtab :: Monad m => Title m -> Title m -> LaTeX m subparagraphtab t1 = comm4 "subparagraph" [t1] part :: Monad m => Title m -> LaTeX m part = comm1 "part" part_ :: Monad m => Title m -> LaTeX m part_ = comm1 "part*" parttab :: Monad m => Title m -> Title m -> LaTeX m parttab t1 = comm4 "part" [t1] -- Sections (Report or Book) chapter :: Monad m => Title m -> LaTeX m chapter = comm1 "chapter" chapter_ :: Monad m => Title m -> LaTeX m chapter_ = comm1 "chapter*" chaptertab :: Monad m => Title m -> Title m -> LaTeX m chaptertab t1 = comm4 "chapter" [t1] -- Sections (Others) -- | Generate the appendix. appendix :: Monad m => LaTeX m appendix = comm0 "appendix" -- | Generate the title page. maketitle :: Monad m => LaTeX m maketitle = comm0 "maketitle" -- | Generate the table of contents. tableofcontents :: Monad m => LaTeX m tableofcontents = comm0 "tableofcontents" -- For Book Class frontmatter :: Monad m => LaTeX m frontmatter = comm0 "frontmatter" mainmatter :: Monad m => LaTeX m mainmatter = comm0 "mainmatter" backmatter :: Monad m => LaTeX m backmatter = comm0 "backmatter" -- Cross References label :: Monad m => Marker m -> LaTeX m label = comm1 "label" ref :: Monad m => Marker m -> LaTeX m ref = comm1 "ref" pageref :: Monad m => Marker m -> LaTeX m pageref = comm1 "pageref" -- Footnotes -- | Adds a given text to the page's footnote. footnote :: Monad m => Text m -> LaTeX m footnote = comm1 "footnote" -- Emphasized -- | Underlines a text. underline :: Monad m => Text m -> LaTeX m underline = comm1 "underline" -- | Emphasizes a text. emph :: Monad m => Text m -> LaTeX m emph = comm1 "emph" -- Environments -- | Environment for create simple lists. See 'item'. itemize :: Monad m => LaTeX m -> LaTeX m itemize = env "itemize" enumerate :: Monad m => LaTeX m -> LaTeX m enumerate = env "enumerate" description :: Monad m => LaTeX m -> LaTeX m description = env "description" -- | Create a list item. Optional argument is used to change its icon. -- -- Example: -- -- > item [\"-\"] \"Item content.\" -- item :: Monad m => [ItemOption m] -> LaTeX m item = comm3 "item" -- | Left alignment. flushleft :: Monad m => LaTeX m -> LaTeX m flushleft = env "flushleft" -- | Right alignment. flushright :: Monad m => LaTeX m -> LaTeX m flushright = env "flushright" -- | Center alignment. center :: Monad m => LaTeX m -> LaTeX m center = env "center" -- | Quote from a text. quote :: Monad m => LaTeX m -> LaTeX m quote = env "quote" -- | Like 'quote', but indenting the first line of each paragraph. quotation :: Monad m => LaTeX m -> LaTeX m quotation = env "quotation" verse :: Monad m => LaTeX m -> LaTeX m verse = env "verse" -- | Use 'abstract' to create an abstract, containing the argument's text. abstract :: Monad m => LaTeX m -> LaTeX m abstract = env "abstract" -- | A text within the 'verbatim' environment has monospaced font -- and no commands or environments will be executed. verbatim :: Monad m => LaTeX m -> LaTeX m verbatim = env "verbatim" -- | Like 'verbatim', but it makes visible the spaces. verbatim_ :: Monad m => LaTeX m -> LaTeX m verbatim_ = env "verbatim*" sep :: Monad m => LaTeX m -> LaTeX m sep = between "|" "|" -- | An inline version of 'verbatim'. verb :: Monad m => LaTeX m -> LaTeX m verb = (comm0_ "verb" >>) . sep -- | An inline version of 'verbatim_'. verb_ :: Monad m => LaTeX m -> LaTeX m verb_ = (comm0_ "verb*" >>) . sep -- Floating Bodies figure :: Monad m => [PlacementSpecifier m] -> LaTeX m -> LaTeX m figure = env2 "figure" table :: Monad m => [PlacementSpecifier m] -> LaTeX m -> LaTeX m table = env2 "table" caption :: Monad m => Text m -> LaTeX m caption = comm1 "caption" listoffigures :: Monad m => LaTeX m listoffigures = comm0 "listoffigures" listoftables :: Monad m => LaTeX m listoftables = comm0 "listoftables" clearpage :: Monad m => LaTeX m clearpage = comm0 "clearpage" cleardoublepage :: Monad m => LaTeX m cleardoublepage = "cleardoblepage" -- Customizing newcommand :: Monad m => Name m -> [Int] -> LaTeX m -> LaTeX m newcommand n i = comm6 "newcommand" n (map lxany i) renewcommand :: Monad m => Name m -> [Int] -> LaTeX m -> LaTeX m renewcommand n i = comm6 "renewcommand" n (map lxany i) providecommand :: Monad m => Name m -> [Int] -> LaTeX m -> LaTeX m providecommand n i = comm6 "providecommand" n (map lxany i) newenvironment :: Monad m => Name m -> [Int] -> LaTeX m -> LaTeX m -> LaTeX m newenvironment n i = comm7 "newenvironment" n (map lxany i) ignorespaces :: Monad m => LaTeX m ignorespaces = comm0 "ignorespaces" ignorespacesafterend :: Monad m => LaTeX m ignorespacesafterend = comm0 "ignorespacesafterend" providesPackage :: Monad m => Name m -> LaTeX m providesPackage = comm1 "ProvidesPackage" -- Fonts -- $fontslabel -- #Fonts# -- | Roman font textrm :: Monad m => LaTeX m -> LaTeX m textrm = comm1 "textrm" -- | Monospaced font texttt :: Monad m => LaTeX m -> LaTeX m texttt = comm1 "texttt" -- | Medium font textmd :: Monad m => LaTeX m -> LaTeX m textmd = comm1 "textmd" -- | Upright font textup :: Monad m => LaTeX m -> LaTeX m textup = comm1 "textup" -- | Slanted font textsl :: Monad m => LaTeX m -> LaTeX m textsl = comm1 "textsl" -- | Sans Serif font textsf :: Monad m => LaTeX m -> LaTeX m textsf = comm1 "textsf" -- | Bold font textbf :: Monad m => LaTeX m -> LaTeX m textbf = comm1 "textbf" -- | Italic font textit :: Monad m => LaTeX m -> LaTeX m textit = comm1 "textit" -- | Small Caps font textsc :: Monad m => LaTeX m -> LaTeX m textsc = comm1 "textsc" -- | Default font textnormal :: Monad m => LaTeX m -> LaTeX m textnormal = comm1 "textnormal" -- Font Sizes -- $fontsize -- Differents fonts size are sorted from lowest to highest. tiny :: Monad m => LaTeX m -> LaTeX m tiny = comm8 "tiny" scriptsize :: Monad m => LaTeX m -> LaTeX m scriptsize = comm8 "scriptsize" footnotesize :: Monad m => LaTeX m -> LaTeX m footnotesize = comm8 "footnotesize" small :: Monad m => LaTeX m -> LaTeX m small = comm8 "small" normalsize :: Monad m => LaTeX m -> LaTeX m normalsize = comm8 "normalsize" large :: Monad m => LaTeX m -> LaTeX m large = comm8 "large" large2 :: Monad m => LaTeX m -> LaTeX m large2 = comm8 "Large" large3 :: Monad m => LaTeX m -> LaTeX m large3 = comm8 "LARGE" huge :: Monad m => LaTeX m -> LaTeX m huge = comm8 "huge" huge2 :: Monad m => LaTeX m -> LaTeX m huge2 = comm8 "Huge" -- par :: Monad m => LaTeX m par = comm0 "par" -- Spacing linespread :: Monad m => Float -> LaTeX m linespread = comm1 "linespread" . lxany -- | Creates an horizontal spaces with length specified by the argument. -- See "Text.LaTeX.Arguments#Measures" to create a correct argument. hspace :: Monad m => LaTeX m -> LaTeX m hspace = comm1 "hspace" -- | Same as 'hspace', but it ignores start or end of lines. hspace_ :: Monad m => LaTeX m -> LaTeX m hspace_ = comm1 "hspace*" -- | Vertical version of 'hspace'. Useful to separate two paragraphs. vspace :: Monad m => LaTeX m -> LaTeX m vspace = comm1 "vspace" -- | Same as 'vspace', but it ignores start or end of pages. vspace_ :: Monad m => LaTeX m -> LaTeX m vspace_ = comm1 "vspace*" stretch :: Monad m => Int -> LaTeX m stretch = comm1 "stretch" . lxany -- | Like 'vspace', but for lines of the same paragraph. -- 'bigskip' and 'smallskip' use 'skip' with a predefined argument. skip :: Monad m => LaTeX m -> LaTeX m skip = mappend lnbk . brackets bigskip :: Monad m => LaTeX m bigskip = comm0 "bigskip" smallskip :: Monad m => LaTeX m smallskip = comm0 "smallskip" -- Boxes mbox :: Monad m => LaTeX m -> LaTeX m mbox = comm1 "mbox" mbox_ :: Monad m => LaTeX m mbox_ = mbox "" fbox :: Monad m => LaTeX m -> LaTeX m fbox = comm1 "fbox" parbox :: Monad m => [Char] -> Width m -> LaTeX m -> LaTeX m parbox c = comm9 "parbox" (if null c then [] else [fromString c]) minipage :: Monad m => [Char] -> Width m -> LaTeX m -> LaTeX m minipage c = env3 "minipage" (if null c then [] else [fromString c]) makebox :: Monad m => [Width m] -> [Char] -> LaTeX m -> LaTeX m makebox w c = comm10 "makebox" w (if null c then [] else [fromString c]) framebox :: Monad m => [Width m] -> [Char] -> LaTeX m -> LaTeX m framebox w c = comm10 "framebox" w (if null c then [] else [fromString c]) raisebox :: Monad m => Lift m -> [Extend m] -> [Extend m] -> LaTeX m -> LaTeX m raisebox = comm11 "raisebox" -- Others protect :: Monad m => LaTeX m protect = comm0_ "protect" phantom :: Monad m => LaTeX m -> LaTeX m phantom = comm1 "phantom" -- Tabular m type Tabular m = LaTeX m cjustified :: Monad m => Width m -> LaTeX m cjustified = ("p">>) . braces csep :: Monad m => LaTeX m -> LaTeX m csep = ("@">>) . braces -- | The 'tabular' environment can be used to creates tables. -- -- * First argument specifies vertical position: -- @\"c\"@ (center), -- @\"t\"@ (top) and -- @\"b\"@ (bottom). -- Example: @[\"t\"]@ -- -- * Second argument specifies table's format: -- @\"l\"@ (left-aligned text column), -- @\"r\"@ (right-aligned text column), -- @\"c\"@ (center text column), -- 'cjustified' (justified text column) and -- @\"|\"@ (vertical line). -- Example: @\"|l|r|\"@ -- -- * Third argument refers to table's content: -- 'hline' inserts an horizontal line, -- 'cline' inserts a partial horizontal line, -- ('&') separates columns and -- ('//') separates rows. tabular :: Monad m => [LaTeX m] -> LaTeX m -> LaTeX m -> Tabular m tabular = env3 "tabular" (&) :: Monad m => LaTeX m -> LaTeX m -> LaTeX m (&) = mid " & " (//) :: Monad m => LaTeX m -> LaTeX m -> LaTeX m (//) = mid $ lnbk >> newline -- | Insert an horizontal line in a 'tabular'. hline :: Monad m => LaTeX m hline = comm0 "hline" -- | Insert a partial horizontal line in a 'tabular'. cline :: Monad m => Int -- ^ Start column -> Int -- ^ End column -> LaTeX m cline n m = comm1 "cline" $ lxany n - lxany m multicolumn :: Monad m => Int -> LaTeX m -> LaTeX m -> LaTeX m multicolumn n = comm12 "multicolumn" $ lxany n type LxMatrix m = [[LaTeX m]] -- | A matrix version of 'tabular'. -- First and second arguments have the same meaning. -- The generated 'tabular' has the same rows and columns as the matrix. matrixTab :: Monad m => [LaTeX m] -> LaTeX m -> LxMatrix m -> Tabular m matrixTab p spec m = let f = tabular p spec . foldr1 (//) . map (foldr1 (&)) in if sum (map length m) == 0 then "" else f m