{-# LANGUAGE OverloadedStrings #-}

-- | This module is the /Prelude/ of LaTeX functions.
--   It includes commands, environments, and some other
--   useful abstractions, that don't require you to
--   import additional LaTeX packages.
module Text.LaTeX.Base.Commands
 ( -- * Basic functions
   raw , between , comment , (%:)
   -- * Preamble commands
 , title
 , author
 , date
 , institute
 , thanks
 , documentclass
 , usepackage
 , linespread
   -- ** Classes
   -- *** Document classes
 , article
 , proc
 , report
 , minimal
 , book
 , slides
   -- *** Class options
 , ClassOption (..)
 , customopt
 , draft
 , titlepage
 , notitlepage
 , onecolumn
 , twocolumn
 , oneside
 , twoside
 , landscape
 , openright
 , openany
 , fleqn
 , leqno
   -- ** Paper sizes
 , PaperType (..)
 , a0paper
 , a1paper
 , a2paper
 , a3paper
 , a4paper
 , a5paper
 , a6paper
 , b0paper
 , b1paper
 , b2paper
 , b3paper
 , b4paper
 , b5paper
 , b6paper
 , letterpaper
 , executivepaper
 , legalpaper
   -- ** Page styles
 , pagestyle
 , thispagestyle
 , plain
 , headings
 , empty
 , myheadings
 , markboth
 , markright
   -- * Body commands
 , document
 , maketitle
   -- ** Document structure
 , tableofcontents
 , abstract
 , appendix
   -- *** Sections
 , part
 , chapter
 , section
 , section'
 , subsection
 , subsection'
 , subsubsection
 , subsubsection'
 , paragraph
 , subparagraph
   -- ** Logos & symbols
 , today
 , thePage
 , tex
 , latex
 , laTeX2
 , laTeXe
 , ldots
 , vdots
 , ddots
 -- *** HaTeX specific
 , hatex
 , hatex3
 , version
 , hatex_version
 -- ** Document layout
 , par
 , newline
 , lnbk
 , lnbk_
 , lnbkspc
 , lnbkspc_
 , newpage
 , cleardoublepage
 , clearpage
 , linebreak
 , nolinebreak
 , pagebreak
 , nopagebreak
 , hspace
 , hspace_
 , vspace
 , vspace_
 , addvspace
 , quad, qquad
 , hfill
 , vfill
 , dotfill
 , hrulefill
 , stretch
 , smallskip
 , medskip
 , bigskip
 , baselineskip
 , indent
 , noindent
   -- *** Document measures
 , textwidth
 , textheight
 , linewidth
   -- ** Formatting text
 , verbatim , verb
   -- *** Fonts
   --
   -- Different font styles.
 , textbf
 , textit
 , texttt
 , textrm
 , textsf
 , textmd
 , textup
 , textsl
 , textsc
 , textnormal
 , underline
 , emph
   -- *** Sizes
   --
   -- | Sizes are sorted from smallest to biggest.
 , tiny
 , scriptsize
 , footnotesize
 , small
 , normalsize
 , large
 , large2
 , large3
 , huge
 , huge2
   -- ** Environments
   -- | Math environments, such as @equation@, defined in "Text.LaTeX.Packages.AMSMath".
 , enumerate
 , itemize
 , item
 , flushleft
 , flushright
 , center
 , quote
 , verse
 , cite
 , description
 , minipage
 , figure
 , table
   -- ** Page numbering
 , pagenumbering
 , arabic
 , roman
 , roman_
 , alph
 , alph_
   -- ** Boxes
 , mbox
 , fbox
 , parbox
 , framebox
 , makebox
 , raisebox
 , rule
   -- ** Cross references
 , caption
 , label
 , ref
 , pageref
   -- ** Tables
 , tabular
 , tabularnewline
 , tabularnewlineSpc
 , arraybackslash
 , array
 , (&)
 , hline
 , cline
 , multicolumn
   -- *** Special tables
 , matrixTabular
   -- ** Others
 , centering
 , raggedleft
 , raggedright
 , footnote
 , footnotemark
 , footnotetext
 , stepcounter
 , addtocounter
 , protect
 , hyphenation
 , hyp
 , qts
   -- * Maths commands
 , module Text.LaTeX.Base.Math
   -- * External files
 , input
 , include
   ) where

import Data.String
import Data.Maybe (isNothing, catMaybes)
import Data.Text (toLower)
import qualified Data.Text as T
import Text.LaTeX.Base.Syntax
import Text.LaTeX.Base.Class
import Text.LaTeX.Base.Render
import Text.LaTeX.Base.Types
import Text.LaTeX.Base.Texy
import Text.LaTeX.Base.Math
import Data.Version
import Data.List (find, intercalate,intersperse)
import Data.Matrix (Matrix,nrows,ncols,(!))
--
import Paths_HaTeX

-- | Create a comment.
comment :: LaTeXC l => Text -> l
comment :: forall l. LaTeXC l => Text -> l
comment = forall l. LaTeXC l => LaTeX -> l
fromLaTeX forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> LaTeX
TeXComment

-- | This operator appends a comment after a expression.
--   For example:
--
-- > textbf "I'm just an example." %: "Insert a few words here."
--
-- The implementation is
--
-- > (%:) l = (l <>) . comment
--
-- Since you are writing in Haskell, you may not need to output comments
-- as you can add them in the Haskell source. I added this feature
-- for completeness. It may be useful for debugging the output as well.
(%:) :: LaTeXC l => l -> Text -> l
%: :: forall l. LaTeXC l => l -> Text -> l
(%:) l
l = (l
l forall a. Semigroup a => a -> a -> a
<>) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall l. LaTeXC l => Text -> l
comment

-- I am not sure this is a worth addition to the namespace. If added, maybe
-- it should be with a different name? Although any name that is slightly
-- longer will make 'eol' not cheaper to type than just @comment ""@, which
-- is already really cheap.

-- | Append a blank comment.
-- eol :: LaTeXC l => l
-- eol = comment ""

-- | Generate the title. It normally contains the 'title' name
-- of your document, the 'author'(s) and 'date'.
maketitle :: LaTeXC l => l
maketitle :: forall l. LaTeXC l => l
maketitle = forall l. LaTeXC l => String -> l
comm0 String
"maketitle"

-- | Set the title of your document.
title :: LaTeXC l => l -> l
title :: forall l. LaTeXC l => l -> l
title = forall l. LaTeXC l => String -> l -> l
comm1 String
"title"

-- | Set a date for your document.
date :: LaTeXC l => l -> l
date :: forall l. LaTeXC l => l -> l
date = forall l. LaTeXC l => String -> l -> l
comm1 String
"date"

-- | Set the author(s) of the document.
author :: LaTeXC l => l -> l
author :: forall l. LaTeXC l => l -> l
author = forall l. LaTeXC l => String -> l -> l
comm1 String
"author"

-- | Set either an institute or an organization
-- for the document. It does /not/ work for
-- a document of the 'article' class.
institute :: LaTeXC l => Maybe l -> l -> l
institute :: forall l. LaTeXC l => Maybe l -> l -> l
institute  Maybe l
Nothing = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
l -> String -> [TeXArg] -> LaTeX
TeXComm String
"institute" [LaTeX -> TeXArg
FixArg LaTeX
l]
institute (Just l
s) = forall l. LaTeXC l => (LaTeX -> LaTeX -> LaTeX) -> l -> l -> l
liftL2 (\LaTeX
l1 LaTeX
l2 -> String -> [TeXArg] -> LaTeX
TeXComm String
"institute" [LaTeX -> TeXArg
OptArg LaTeX
l1,LaTeX -> TeXArg
FixArg LaTeX
l2]) l
s

thanks :: LaTeXC l => l -> l
thanks :: forall l. LaTeXC l => l -> l
thanks = forall l. LaTeXC l => String -> l -> l
comm1 String
"thanks"

-- | Import a package. First argument is a list of options for
-- the package named in the second argument.
usepackage :: LaTeXC l => [l] -> PackageName -> l
usepackage :: forall l. LaTeXC l => [l] -> String -> l
usepackage [l]
ls String
pn = forall l. LaTeXC l => ([LaTeX] -> LaTeX) -> [l] -> l
liftListL (\[LaTeX]
ls_ -> String -> [TeXArg] -> LaTeX
TeXComm String
"usepackage" [[LaTeX] -> TeXArg
MOptArg [LaTeX]
ls_ ,LaTeX -> TeXArg
FixArg forall a b. (a -> b) -> a -> b
$ forall a. IsString a => String -> a
fromString String
pn]) [l]
ls

-- | The @LaTeX@ logo.
latex :: LaTeXC l => l
latex :: forall l. LaTeXC l => l
latex = forall l. LaTeXC l => String -> l
comm0 String
"LaTeX"

-- | Start a new paragraph
par :: LaTeXC l => l
par :: forall l. LaTeXC l => l
par = forall l. LaTeXC l => String -> l
comm0 String
"par"

-- | Start a new line. It can be used only in paragraph mode.
newline :: LaTeXC l => l
newline :: forall l. LaTeXC l => l
newline = forall l. LaTeXC l => String -> l
comm0 String
"newline"

part :: LaTeXC l => l -> l
part :: forall l. LaTeXC l => l -> l
part = forall l. LaTeXC l => String -> l -> l
comm1 String
"part"

-- | Start a new chapter with the given title.
chapter :: LaTeXC l => l -> l
chapter :: forall l. LaTeXC l => l -> l
chapter = forall l. LaTeXC l => String -> l -> l
comm1 String
"chapter"

-- | Start a new section with a given title.
section :: LaTeXC l => l -> l
section :: forall l. LaTeXC l => l -> l
section = forall l. LaTeXC l => String -> l -> l
comm1 String
"section"

-- | Start a new unnumbered section with a given title.
section' :: LaTeXC l => l -> l
section' :: forall l. LaTeXC l => l -> l
section' = forall l. LaTeXC l => String -> l -> l
comm1 String
"section*"

-- | Start a new subsection.
subsection :: LaTeXC l => l -> l
subsection :: forall l. LaTeXC l => l -> l
subsection = forall l. LaTeXC l => String -> l -> l
comm1 String
"subsection"

-- | Start a new unnumbered subsection.
subsection' :: LaTeXC l => l -> l
subsection' :: forall l. LaTeXC l => l -> l
subsection' = forall l. LaTeXC l => String -> l -> l
comm1 String
"subsection*"

-- | Start a new sub/sub/section.
subsubsection :: LaTeXC l => l -> l
subsubsection :: forall l. LaTeXC l => l -> l
subsubsection = forall l. LaTeXC l => String -> l -> l
comm1 String
"subsubsection"

-- | Start a new unnumbered sub/sub/section.
subsubsection' :: LaTeXC l => l -> l
subsubsection' :: forall l. LaTeXC l => l -> l
subsubsection' = forall l. LaTeXC l => String -> l -> l
comm1 String
"subsubsection*"

-- | Start a paragraph.
paragraph :: LaTeXC l => l -> l
paragraph :: forall l. LaTeXC l => l -> l
paragraph = forall l. LaTeXC l => String -> l -> l
comm1 String
"paragraph"

-- | Start a subparagraph (minimal level of sectioning).
subparagraph :: LaTeXC l => l -> l
subparagraph :: forall l. LaTeXC l => l -> l
subparagraph = forall l. LaTeXC l => String -> l -> l
comm1 String
"subparagraph"

-- | Create the table of contents, automatically generated
-- from your 'section's, 'subsection's, and related functions.
tableofcontents :: LaTeXC l => l
tableofcontents :: forall l. LaTeXC l => l
tableofcontents = forall l. LaTeXC l => String -> l
comm0 String
"tableofcontents"

appendix :: LaTeXC l => l
appendix :: forall l. LaTeXC l => l
appendix = forall l. LaTeXC l => String -> l
comm0 String
"appendix"

-- | An item of a list (see 'enumerate' or 'itemize').
--   The optional argument sets the design of the item.
item :: LaTeXC l => Maybe l -> l
item :: forall l. LaTeXC l => Maybe l -> l
item Maybe l
Nothing    = forall l. LaTeXC l => String -> l
commS String
"item "
item (Just l
opt) = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL (\LaTeX
opt_ -> String -> [TeXArg] -> LaTeX
TeXComm String
"item" [LaTeX -> TeXArg
OptArg LaTeX
opt_]) l
opt

-- | Environment of ordered lists. Use 'item' to start each list
--   item.
enumerate :: LaTeXC l => l -> l
enumerate :: forall l. LaTeXC l => l -> l
enumerate = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ String -> [TeXArg] -> LaTeX -> LaTeX
TeXEnv String
"enumerate" []

-- | Environment of unordered lists. Use 'item' to start each list
--   item.
itemize :: LaTeXC l => l -> l
itemize :: forall l. LaTeXC l => l -> l
itemize = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ String -> [TeXArg] -> LaTeX -> LaTeX
TeXEnv String
"itemize" []

description :: LaTeXC l => l -> l
description :: forall l. LaTeXC l => l -> l
description = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ String -> [TeXArg] -> LaTeX -> LaTeX
TeXEnv String
"description" []

-- | Left-justify the argument.
flushleft :: LaTeXC l => l -> l
flushleft :: forall l. LaTeXC l => l -> l
flushleft = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ String -> [TeXArg] -> LaTeX -> LaTeX
TeXEnv String
"flushleft" []

-- | Right-justify the argument.
flushright :: LaTeXC l => l -> l
flushright :: forall l. LaTeXC l => l -> l
flushright = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ String -> [TeXArg] -> LaTeX -> LaTeX
TeXEnv String
"flushright" []

-- | Center-justify the argument.
center :: LaTeXC l => l -> l
center :: forall l. LaTeXC l => l -> l
center = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ String -> [TeXArg] -> LaTeX -> LaTeX
TeXEnv String
"center" []

quote :: LaTeXC l => l -> l
quote :: forall l. LaTeXC l => l -> l
quote = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ String -> [TeXArg] -> LaTeX -> LaTeX
TeXEnv String
"quote" []

verse :: LaTeXC l => l -> l
verse :: forall l. LaTeXC l => l -> l
verse = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ String -> [TeXArg] -> LaTeX -> LaTeX
TeXEnv String
"verse" []

-- | Minipage environment.
minipage :: LaTeXC l =>
            Maybe Pos -- ^ Optional position
         -> l         -- ^ Width
         -> l         -- ^ Minipage content
         -> l
minipage :: forall l. LaTeXC l => Maybe Pos -> l -> l -> l
minipage Maybe Pos
Nothing  = forall l. LaTeXC l => (LaTeX -> LaTeX -> LaTeX) -> l -> l -> l
liftL2 forall a b. (a -> b) -> a -> b
$ \LaTeX
ts -> String -> [TeXArg] -> LaTeX -> LaTeX
TeXEnv String
"minipage" [ LaTeX -> TeXArg
FixArg LaTeX
ts ]
minipage (Just Pos
p) = forall l. LaTeXC l => (LaTeX -> LaTeX -> LaTeX) -> l -> l -> l
liftL2 forall a b. (a -> b) -> a -> b
$ \LaTeX
ts -> String -> [TeXArg] -> LaTeX -> LaTeX
TeXEnv String
"minipage" [ LaTeX -> TeXArg
OptArg forall a b. (a -> b) -> a -> b
$ forall a l. (Render a, LaTeXC l) => a -> l
rendertex Pos
p , LaTeX -> TeXArg
FixArg LaTeX
ts ]

-- | Figure environment. Use this for floating "Text.LaTeX.Packages.Graphicx"
--   content out of the text block and giving it a 'caption'. The figure can be
--   referred to with 'ref' from elsewhere in the document.
figure :: LaTeXC l =>
          Maybe Pos -- ^ Optional position.
       -> l         -- ^ Figure content (should usually contain
                    --   'Text.LaTeX.Packages.Graphicx.includegraphics',
                    --   'caption' and 'label').
       -> l
figure :: forall l. LaTeXC l => Maybe Pos -> l -> l
figure Maybe Pos
Nothing  = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ String -> [TeXArg] -> LaTeX -> LaTeX
TeXEnv String
"figure" []
figure (Just Pos
p) = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ String -> [TeXArg] -> LaTeX -> LaTeX
TeXEnv String
"figure" [ LaTeX -> TeXArg
OptArg forall a b. (a -> b) -> a -> b
$ Text -> LaTeX
TeXRaw forall a b. (a -> b) -> a -> b
$ forall a. Render a => a -> Text
render Pos
p ]

-- | Table environment. Use this for floating a 'tabular' out of the text block and
--   giving it a 'caption'. The table can be referred to with 'ref'.
table :: LaTeXC l =>
          [Pos] -- ^ Position preferences. Leave empty to use default.
       -> l         -- ^ Table content (assemble with 'tabular'/'matrixTabular',
                    --   'caption' and 'label').
       -> l
table :: forall l. LaTeXC l => [Pos] -> l -> l
table [] = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ String -> [TeXArg] -> LaTeX -> LaTeX
TeXEnv String
"table" []
table [Pos]
ps = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ String -> [TeXArg] -> LaTeX -> LaTeX
TeXEnv String
"table" [ LaTeX -> TeXArg
OptArg forall a b. (a -> b) -> a -> b
$ Text -> LaTeX
TeXRaw forall a b. (a -> b) -> a -> b
$ forall a. Render a => [a] -> Text
renderAppend [Pos]
ps ]

-- | Abstract section.
abstract :: LaTeXC l => l -> l
abstract :: forall l. LaTeXC l => l -> l
abstract = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ String -> [TeXArg] -> LaTeX -> LaTeX
TeXEnv String
"abstract" []

cite :: LaTeXC l => l -> l
cite :: forall l. LaTeXC l => l -> l
cite = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
l -> String -> [TeXArg] -> LaTeX
TeXComm String
"cite" [LaTeX -> TeXArg
FixArg LaTeX
l]

-- Document class

-- | A class option to be passed to the 'documentclass' function.
data ClassOption =
   Draft
 | TitlePage
 | NoTitlePage
 | OneColumn
 | TwoColumn
 | OneSide
 | TwoSide
 | Landscape
 | OpenRight
 | OpenAny
 | Fleqn
 | Leqno
 | FontSize Measure
 | Paper PaperType
 | CustomOption String
   deriving Int -> ClassOption -> ShowS
[ClassOption] -> ShowS
ClassOption -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ClassOption] -> ShowS
$cshowList :: [ClassOption] -> ShowS
show :: ClassOption -> String
$cshow :: ClassOption -> String
showsPrec :: Int -> ClassOption -> ShowS
$cshowsPrec :: Int -> ClassOption -> ShowS
Show

instance Render ClassOption where
 render :: ClassOption -> Text
render (FontSize Measure
m) = forall a. Render a => a -> Text
render Measure
m
 render (Paper PaperType
pt) = Text -> Text
toLower (forall a. Render a => a -> Text
render PaperType
pt) forall a. Semigroup a => a -> a -> a
<> Text
"paper"
 render (CustomOption String
str) = forall a. IsString a => String -> a
fromString String
str
 render ClassOption
co = Text -> Text
toLower forall a b. (a -> b) -> a -> b
$ forall a. IsString a => String -> a
fromString forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show ClassOption
co

customopt :: String -> ClassOption
customopt :: String -> ClassOption
customopt = String -> ClassOption
CustomOption

instance IsString ClassOption where
 fromString :: String -> ClassOption
fromString = String -> ClassOption
customopt

-- | LaTeX available paper types.
data PaperType =
   A0 | A1 | A2 | A3 | A4 | A5 | A6
 | B0 | B1 | B2 | B3 | B4 | B5 | B6
 | Letter | Executive | Legal
   deriving Int -> PaperType -> ShowS
[PaperType] -> ShowS
PaperType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PaperType] -> ShowS
$cshowList :: [PaperType] -> ShowS
show :: PaperType -> String
$cshow :: PaperType -> String
showsPrec :: Int -> PaperType -> ShowS
$cshowsPrec :: Int -> PaperType -> ShowS
Show

instance Render PaperType where

-- | Set the document class. Needed in all documents.
documentclass :: LaTeXC l =>
                [ClassOption] -- ^ Class options
              -> ClassName    -- ^ Class name
              -> l
documentclass :: forall l. LaTeXC l => [ClassOption] -> String -> l
documentclass [ClassOption]
opts String
cn = forall l. LaTeXC l => LaTeX -> l
fromLaTeX forall a b. (a -> b) -> a -> b
$ String -> [TeXArg] -> LaTeX
TeXComm String
"documentclass" [[LaTeX] -> TeXArg
MOptArg forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a l. (Render a, LaTeXC l) => a -> l
rendertex [ClassOption]
opts , LaTeX -> TeXArg
FixArg forall a b. (a -> b) -> a -> b
$ forall a. IsString a => String -> a
fromString String
cn]

article :: ClassName
article :: String
article = String
"article"

proc :: ClassName
proc :: String
proc = String
"proc"

minimal :: ClassName
minimal :: String
minimal = String
"minimal"

report :: ClassName
report :: String
report = String
"report"

book :: ClassName
book :: String
book = String
"book"

slides :: ClassName
slides :: String
slides = String
"slides"

a0paper :: ClassOption
a0paper :: ClassOption
a0paper = PaperType -> ClassOption
Paper PaperType
A0

a1paper :: ClassOption
a1paper :: ClassOption
a1paper = PaperType -> ClassOption
Paper PaperType
A1

a2paper :: ClassOption
a2paper :: ClassOption
a2paper = PaperType -> ClassOption
Paper PaperType
A2

a3paper :: ClassOption
a3paper :: ClassOption
a3paper = PaperType -> ClassOption
Paper PaperType
A3

a4paper :: ClassOption
a4paper :: ClassOption
a4paper = PaperType -> ClassOption
Paper PaperType
A4

a5paper :: ClassOption
a5paper :: ClassOption
a5paper = PaperType -> ClassOption
Paper PaperType
A5

a6paper :: ClassOption
a6paper :: ClassOption
a6paper = PaperType -> ClassOption
Paper PaperType
A6

b0paper :: ClassOption
b0paper :: ClassOption
b0paper = PaperType -> ClassOption
Paper PaperType
B0

b1paper :: ClassOption
b1paper :: ClassOption
b1paper = PaperType -> ClassOption
Paper PaperType
B1

b2paper :: ClassOption
b2paper :: ClassOption
b2paper = PaperType -> ClassOption
Paper PaperType
B2

b3paper :: ClassOption
b3paper :: ClassOption
b3paper = PaperType -> ClassOption
Paper PaperType
B3

b4paper :: ClassOption
b4paper :: ClassOption
b4paper = PaperType -> ClassOption
Paper PaperType
B4

b5paper :: ClassOption
b5paper :: ClassOption
b5paper = PaperType -> ClassOption
Paper PaperType
B5

b6paper :: ClassOption
b6paper :: ClassOption
b6paper = PaperType -> ClassOption
Paper PaperType
B6

letterpaper :: ClassOption
letterpaper :: ClassOption
letterpaper = PaperType -> ClassOption
Paper PaperType
Letter

executivepaper :: ClassOption
executivepaper :: ClassOption
executivepaper = PaperType -> ClassOption
Paper PaperType
Executive

legalpaper :: ClassOption
legalpaper :: ClassOption
legalpaper = PaperType -> ClassOption
Paper PaperType
Legal

draft :: ClassOption
draft :: ClassOption
draft = ClassOption
Draft

-- | Typesets displayed formulae left-aligned instead of centred.
fleqn :: ClassOption
fleqn :: ClassOption
fleqn = ClassOption
Fleqn

-- | Places the numbering of formulae on the left hand side instead of the right.
leqno :: ClassOption
leqno :: ClassOption
leqno = ClassOption
Leqno

titlepage :: ClassOption
titlepage :: ClassOption
titlepage = ClassOption
TitlePage

notitlepage :: ClassOption
notitlepage :: ClassOption
notitlepage = ClassOption
NoTitlePage

onecolumn :: ClassOption
onecolumn :: ClassOption
onecolumn = ClassOption
OneColumn

twocolumn :: ClassOption
twocolumn :: ClassOption
twocolumn = ClassOption
TwoColumn

oneside :: ClassOption
oneside :: ClassOption
oneside = ClassOption
OneSide

twoside :: ClassOption
twoside :: ClassOption
twoside = ClassOption
TwoSide

-- | Changes the layout of the document to print in landscape mode
landscape :: ClassOption
landscape :: ClassOption
landscape = ClassOption
Landscape

-- | Makes chapters begin either only on right hand pages
openright :: ClassOption
openright :: ClassOption
openright = ClassOption
OpenRight

-- | Makes chapters begin on the next page available.
openany :: ClassOption
openany :: ClassOption
openany = ClassOption
OpenAny

-- | The 'document' environment contains the body of the document.
document :: LaTeXC l => l -> l
document :: forall l. LaTeXC l => l -> l
document = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ String -> [TeXArg] -> LaTeX -> LaTeX
TeXEnv String
"document" []

pagenumbering :: LaTeXC l => l -> l
pagenumbering :: forall l. LaTeXC l => l -> l
pagenumbering = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
l -> String -> [TeXArg] -> LaTeX
TeXComm String
"pagenumbering" [LaTeX -> TeXArg
FixArg LaTeX
l]

-- | Arabic numerals.
arabic :: LaTeXC l => l
arabic :: forall l. LaTeXC l => l
arabic = forall l. LaTeXC l => LaTeX -> l
fromLaTeX LaTeX
"arabic"

-- | Lowercase roman numerals.
roman :: LaTeXC l => l
roman :: forall l. LaTeXC l => l
roman = forall l. LaTeXC l => LaTeX -> l
fromLaTeX LaTeX
"roman"

-- | Uppercase roman numerals.
roman_ :: LaTeXC l => l
roman_ :: forall l. LaTeXC l => l
roman_ = forall l. LaTeXC l => LaTeX -> l
fromLaTeX LaTeX
"Roman"

-- | Lowercase letters.
alph :: LaTeXC l => l
alph :: forall l. LaTeXC l => l
alph = forall l. LaTeXC l => LaTeX -> l
fromLaTeX LaTeX
"alph"

-- | Uppercase letters.
alph_ :: LaTeXC l => l
alph_ :: forall l. LaTeXC l => l
alph_ = forall l. LaTeXC l => LaTeX -> l
fromLaTeX LaTeX
"Alph"

-- Page styles

pagestyle :: LaTeXC l => PageStyle -> l
pagestyle :: forall l. LaTeXC l => String -> l
pagestyle String
ps = forall l. LaTeXC l => LaTeX -> l
fromLaTeX forall a b. (a -> b) -> a -> b
$ String -> [TeXArg] -> LaTeX
TeXComm String
"pagestyle" [LaTeX -> TeXArg
FixArg forall a b. (a -> b) -> a -> b
$ forall a. IsString a => String -> a
fromString String
ps]

thispagestyle :: LaTeXC l => PageStyle -> l
thispagestyle :: forall l. LaTeXC l => String -> l
thispagestyle String
ps = forall l. LaTeXC l => LaTeX -> l
fromLaTeX forall a b. (a -> b) -> a -> b
$ String -> [TeXArg] -> LaTeX
TeXComm String
"thispagestyle" [LaTeX -> TeXArg
FixArg forall a b. (a -> b) -> a -> b
$ forall a. IsString a => String -> a
fromString String
ps]

plain :: PageStyle
plain :: String
plain = String
"plain"

headings :: PageStyle
headings :: String
headings = String
"headings"

empty :: PageStyle
empty :: String
empty = String
"empty"

myheadings :: PageStyle
myheadings :: String
myheadings = String
"myheadings"

-- | Used in conjunction with 'myheadings' for setting both the left and the right heading.
markboth :: LaTeXC l => l -> l -> l
markboth :: forall l. LaTeXC l => l -> l -> l
markboth = forall l. LaTeXC l => (LaTeX -> LaTeX -> LaTeX) -> l -> l -> l
liftL2 forall a b. (a -> b) -> a -> b
$ \LaTeX
l1 LaTeX
l2 -> String -> [TeXArg] -> LaTeX
TeXComm String
"markboth" [LaTeX -> TeXArg
FixArg LaTeX
l1 , LaTeX -> TeXArg
FixArg LaTeX
l2]

-- | Used in conjunction with 'myheadings' for setting the right heading.
markright :: LaTeXC l => l -> l
markright :: forall l. LaTeXC l => l -> l
markright = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
l -> String -> [TeXArg] -> LaTeX
TeXComm String
"markright" [LaTeX -> TeXArg
FixArg LaTeX
l]

-- | Start a new line. The exactly meaning depends on the context
-- where it is used. In normal running text when it forces a line
-- break it is essentially a shorthand for '\\newline' (does not end
-- horizontal mode or end the paragraph, it just inserts some glue and
-- penalties at that point into the horizontal material so that when
-- the paragraph does end a line break will occur at that point with
-- the short line padded with white space). In alignment environments
-- (like 'tabular'), it starts a new row, so use 'newline' instead to
-- start a new line.
lnbk  :: LaTeXC l => l
lnbk :: forall l. LaTeXC l => l
lnbk = forall l. LaTeXC l => LaTeX -> l
fromLaTeX forall a b. (a -> b) -> a -> b
$ Maybe Measure -> Bool -> LaTeX
TeXLineBreak forall a. Maybe a
Nothing Bool
False

-- | Like 'lnbk', 'lnbk_' introduces a line break, but preventing a
-- page break.
lnbk_ :: LaTeXC l => l
lnbk_ :: forall l. LaTeXC l => l
lnbk_ = forall l. LaTeXC l => LaTeX -> l
fromLaTeX forall a b. (a -> b) -> a -> b
$ Maybe Measure -> Bool -> LaTeX
TeXLineBreak forall a. Maybe a
Nothing Bool
True

-- | Like 'lnbk', introduces a line break. But it has an argument that
-- specifies how much extra vertical space is to be inserted before
-- the next line. This can be a negative amount.
lnbkspc :: LaTeXC l => Measure -> l
lnbkspc :: forall l. LaTeXC l => Measure -> l
lnbkspc Measure
extraSpace = forall l. LaTeXC l => LaTeX -> l
fromLaTeX forall a b. (a -> b) -> a -> b
$ Maybe Measure -> Bool -> LaTeX
TeXLineBreak (forall a. a -> Maybe a
Just Measure
extraSpace) Bool
False

-- | Like 'lnbkspc', 'lnbkspc_' introduces a line break with an extra
-- vertical space, but preventing a page break.
lnbkspc_ :: LaTeXC l => Measure -> l
lnbkspc_ :: forall l. LaTeXC l => Measure -> l
lnbkspc_ Measure
extraSpace = forall l. LaTeXC l => LaTeX -> l
fromLaTeX forall a b. (a -> b) -> a -> b
$ Maybe Measure -> Bool -> LaTeX
TeXLineBreak (forall a. a -> Maybe a
Just Measure
extraSpace) Bool
True

hyp :: LaTeXC l => l
hyp :: forall l. LaTeXC l => l
hyp = forall l. LaTeXC l => LaTeX -> l
fromLaTeX forall a b. (a -> b) -> a -> b
$ String -> LaTeX
TeXCommS String
"-"

cleardoublepage :: LaTeXC l => l
cleardoublepage :: forall l. LaTeXC l => l
cleardoublepage = forall l. LaTeXC l => String -> l
comm0 String
"cleardoublepage"

clearpage :: LaTeXC l => l
clearpage :: forall l. LaTeXC l => l
clearpage = forall l. LaTeXC l => String -> l
comm0 String
"clearpage"

newpage :: LaTeXC l => l
newpage :: forall l. LaTeXC l => l
newpage = forall l. LaTeXC l => String -> l
comm0 String
"newpage"

-- | Request to break the current line at the point of the command
-- stretching the line so that it extends to the right margin. The
-- number must be a number from 0 to 4. The higher the number, the
-- more insistent the request is (0 means it will be easily ignored
-- and 4 means do it anyway). When this line break option is used,
-- LaTeX will try to produce the best line breaks possible.
linebreak :: LaTeXC l => l -> l
linebreak :: forall l. LaTeXC l => l -> l
linebreak = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
l -> String -> [TeXArg] -> LaTeX
TeXComm String
"linebreak" [LaTeX -> TeXArg
OptArg LaTeX
l]

-- | Like 'linebreak', but prevents a like break instead of requesting
-- one.
nolinebreak :: LaTeXC l => l -> l
nolinebreak :: forall l. LaTeXC l => l -> l
nolinebreak = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
l -> String -> [TeXArg] -> LaTeX
TeXComm String
"nolinebreak" [LaTeX -> TeXArg
OptArg LaTeX
l]

pagebreak :: LaTeXC l => Maybe l -> l
pagebreak :: forall l. LaTeXC l => Maybe l -> l
pagebreak = forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall l. LaTeXC l => String -> l
comm0 String
"pagebreak")
            forall a b. (a -> b) -> a -> b
$ forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
l -> String -> [TeXArg] -> LaTeX
TeXComm String
"pagebreak" [LaTeX -> TeXArg
OptArg LaTeX
l]

nopagebreak :: LaTeXC l => Maybe l -> l
nopagebreak :: forall l. LaTeXC l => Maybe l -> l
nopagebreak = forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall l. LaTeXC l => String -> l
comm0 String
"nopagebreak")
            forall a b. (a -> b) -> a -> b
$ forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
l -> String -> [TeXArg] -> LaTeX
TeXComm String
"nopagebreak" [LaTeX -> TeXArg
OptArg LaTeX
l]

hyphenation :: LaTeXC l => l -> l
hyphenation :: forall l. LaTeXC l => l -> l
hyphenation = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
l -> String -> [TeXArg] -> LaTeX
TeXComm String
"hyphenation" [LaTeX -> TeXArg
FixArg LaTeX
l]

mbox :: LaTeXC l => l -> l
mbox :: forall l. LaTeXC l => l -> l
mbox = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
l -> String -> [TeXArg] -> LaTeX
TeXComm String
"mbox" [LaTeX -> TeXArg
FixArg LaTeX
l]

fbox :: LaTeXC l => l -> l
fbox :: forall l. LaTeXC l => l -> l
fbox = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
l -> String -> [TeXArg] -> LaTeX
TeXComm String
"fbox" [LaTeX -> TeXArg
FixArg LaTeX
l]

-- | Render the date at compilation time.
today :: LaTeXC l => l
today :: forall l. LaTeXC l => l
today = forall l. LaTeXC l => String -> l
comm0 String
"today"

-- | Render the current page.
thePage :: LaTeXC l => l
thePage :: forall l. LaTeXC l => l
thePage = forall l. LaTeXC l => String -> l
comm0 String
"thepage"

-- | TeX logo.
tex :: LaTeXC l => l
tex :: forall l. LaTeXC l => l
tex = forall l. LaTeXC l => String -> l
comm0 String
"TeX"

-- | LaTeX logo.
laTeX2 :: LaTeXC l => l
laTeX2 :: forall l. LaTeXC l => l
laTeX2 = forall l. LaTeXC l => String -> l
comm0 String
"LaTeX"

laTeXe :: LaTeXC l => l
laTeXe :: forall l. LaTeXC l => l
laTeXe = forall l. LaTeXC l => String -> l
comm0 String
"LaTeXe"

-- | Horizontal dots.
ldots :: LaTeXC l => l
ldots :: forall l. LaTeXC l => l
ldots = forall l. LaTeXC l => String -> l
comm0 String
"ldots"

-- | Vertical dots.
vdots :: LaTeXC l => l
vdots :: forall l. LaTeXC l => l
vdots = forall l. LaTeXC l => String -> l
comm0 String
"vdots"

-- | Diagonal dots.
ddots :: LaTeXC l => l
ddots :: forall l. LaTeXC l => l
ddots = forall l. LaTeXC l => String -> l
comm0 String
"ddots"

-- | Quotation marks.
qts :: LaTeXC l => l -> l
qts :: forall l. LaTeXC l => l -> l
qts l
l = forall m. Monoid m => m -> m -> m -> m
between l
l (forall l. LaTeXC l => Text -> l
raw Text
"``") (forall l. LaTeXC l => Text -> l
raw Text
"''")

centering :: LaTeXC l => l
centering :: forall l. LaTeXC l => l
centering = forall l. LaTeXC l => String -> l
comm0 String
"centering"

raggedleft :: LaTeXC l => l
raggedleft :: forall l. LaTeXC l => l
raggedleft = forall l. LaTeXC l => String -> l
comm0 String
"raggedleft"

raggedright :: LaTeXC l => l
raggedright :: forall l. LaTeXC l => l
raggedright = forall l. LaTeXC l => String -> l
comm0 String
"raggedright"

footnote :: LaTeXC l => l -> l
footnote :: forall l. LaTeXC l => l -> l
footnote = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
l -> String -> [TeXArg] -> LaTeX
TeXComm String
"footnote" [LaTeX -> TeXArg
FixArg LaTeX
l]

-- | Prints a foot note mark but without the actual footnote.
footnotemark :: LaTeXC l => l
footnotemark :: forall l. LaTeXC l => l
footnotemark = forall l. LaTeXC l => String -> l
comm0 String
"footnotemark"

-- | Prints the footnote corresponding to the previous footnotemark.
-- Useful when dealing with footnotes in tabular environment.
footnotetext :: LaTeXC l => l -> l
footnotetext :: forall l. LaTeXC l => l -> l
footnotetext = forall l. LaTeXC l => String -> l -> l
comm1 String
"footnotetext"

-- | Increases by 1 the value of given counter
stepcounter :: LaTeXC l => String -> l
stepcounter :: forall l. LaTeXC l => String -> l
stepcounter = forall l. LaTeXC l => String -> l -> l
comm1 String
"stepcounter" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. IsString a => String -> a
fromString

-- | Increases by `n` the value of given counter `t`
addtocounter :: LaTeXC l => String -> Int -> l
addtocounter :: forall l. LaTeXC l => String -> Int -> l
addtocounter String
t Int
n = forall l. LaTeXC l => String -> l -> l -> l
comm2 String
"addtocounter" (forall a. IsString a => String -> a
fromString String
t) (forall a. IsString a => String -> a
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show forall a b. (a -> b) -> a -> b
$ Int
n)

linespread :: LaTeXC l => Float -> l
linespread :: forall l. LaTeXC l => Float -> l
linespread Float
x = forall l. LaTeXC l => LaTeX -> l
fromLaTeX forall a b. (a -> b) -> a -> b
$ String -> [TeXArg] -> LaTeX
TeXComm String
"linespread" [LaTeX -> TeXArg
FixArg forall a b. (a -> b) -> a -> b
$ forall a l. (Render a, LaTeXC l) => a -> l
rendertex Float
x]

baselineskip :: LaTeXC l => l
baselineskip :: forall l. LaTeXC l => l
baselineskip = forall l. LaTeXC l => String -> l
comm0 String
"baselineskip"

indent :: LaTeXC l => l
indent :: forall l. LaTeXC l => l
indent = forall l. LaTeXC l => String -> l
comm0 String
"indent"

noindent :: LaTeXC l => l
noindent :: forall l. LaTeXC l => l
noindent = forall l. LaTeXC l => String -> l
comm0 String
"noindent"

hspace :: LaTeXC l => Measure -> l
hspace :: forall l. LaTeXC l => Measure -> l
hspace Measure
m = forall l. LaTeXC l => LaTeX -> l
fromLaTeX forall a b. (a -> b) -> a -> b
$ String -> [TeXArg] -> LaTeX
TeXComm String
"hspace" [LaTeX -> TeXArg
FixArg forall a b. (a -> b) -> a -> b
$ forall a l. (Render a, LaTeXC l) => a -> l
rendertex Measure
m]

hspace_ :: LaTeXC l => Measure -> l
hspace_ :: forall l. LaTeXC l => Measure -> l
hspace_ Measure
m = forall l. LaTeXC l => LaTeX -> l
fromLaTeX forall a b. (a -> b) -> a -> b
$ String -> [TeXArg] -> LaTeX
TeXComm String
"hspace*" [LaTeX -> TeXArg
FixArg forall a b. (a -> b) -> a -> b
$ forall a l. (Render a, LaTeXC l) => a -> l
rendertex Measure
m]

-- | Space equal to the current font size (= 18 mu). \(a\quad b\)
quad :: LaTeXC l => l
quad :: forall l. LaTeXC l => l
quad = forall l. LaTeXC l => String -> l
comm0 String
"quad"

-- | Twice of @\quad@ (= 36 mu).  \(a\qquad b\)
qquad :: LaTeXC l => l
qquad :: forall l. LaTeXC l => l
qquad = forall l. LaTeXC l => String -> l
comm0 String
"qquad"


stretch :: LaTeXC l => Double -> l
stretch :: forall l. LaTeXC l => Double -> l
stretch Double
n = forall l. LaTeXC l => LaTeX -> l
fromLaTeX forall a b. (a -> b) -> a -> b
$ String -> [TeXArg] -> LaTeX
TeXComm String
"stretch" [LaTeX -> TeXArg
FixArg forall a b. (a -> b) -> a -> b
$ forall a l. (Render a, LaTeXC l) => a -> l
rendertex Double
n]

-- | Add vertical white space, except at the end of a page.
vspace :: LaTeXC l => Measure -> l
vspace :: forall l. LaTeXC l => Measure -> l
vspace Measure
m = forall l. LaTeXC l => LaTeX -> l
fromLaTeX forall a b. (a -> b) -> a -> b
$ String -> [TeXArg] -> LaTeX
TeXComm String
"vspace" [LaTeX -> TeXArg
FixArg forall a b. (a -> b) -> a -> b
$ forall a l. (Render a, LaTeXC l) => a -> l
rendertex Measure
m]

-- | Add vertical white space, even at the end of a page.
vspace_ :: LaTeXC l => Measure -> l
vspace_ :: forall l. LaTeXC l => Measure -> l
vspace_ Measure
m = forall l. LaTeXC l => LaTeX -> l
fromLaTeX forall a b. (a -> b) -> a -> b
$ String -> [TeXArg] -> LaTeX
TeXComm String
"vspace*" [LaTeX -> TeXArg
FixArg forall a b. (a -> b) -> a -> b
$ forall a l. (Render a, LaTeXC l) => a -> l
rendertex Measure
m]

-- | Add extra vertical white space. In a sequence of 'addvspace' the
-- length of the final white space is given by the maximum of the
-- individual lengths.
addvspace :: LaTeXC l => Measure -> l
addvspace :: forall l. LaTeXC l => Measure -> l
addvspace Measure
m = forall l. LaTeXC l => LaTeX -> l
fromLaTeX forall a b. (a -> b) -> a -> b
$ String -> [TeXArg] -> LaTeX
TeXComm String
"addvspace" [LaTeX -> TeXArg
FixArg forall a b. (a -> b) -> a -> b
$ forall a l. (Render a, LaTeXC l) => a -> l
rendertex Measure
m]

-- | Fill out all available horizontal space.
hfill :: LaTeXC l => l
hfill :: forall l. LaTeXC l => l
hfill = forall l. LaTeXC l => String -> l
comm0 String
"hfill"

-- | Fill out all available vertical space.
vfill :: LaTeXC l => l
vfill :: forall l. LaTeXC l => l
vfill = forall l. LaTeXC l => String -> l
comm0 String
"vfill"

-- | Fill out all available horizontal space with dots.
dotfill :: LaTeXC l => l
dotfill :: forall l. LaTeXC l => l
dotfill = forall l. LaTeXC l => String -> l
comm0 String
"dotfill"

-- | Fill out all available horizontal space with a line.
hrulefill :: LaTeXC l => l
hrulefill :: forall l. LaTeXC l => l
hrulefill = forall l. LaTeXC l => String -> l
comm0 String
"hrulefill"

protect :: LaTeXC l => l -> l
protect :: forall l. LaTeXC l => l -> l
protect l
l = forall l. LaTeXC l => String -> l
commS String
"protect" forall a. Semigroup a => a -> a -> a
<> l
l

textwidth :: LaTeXC l => l
textwidth :: forall l. LaTeXC l => l
textwidth = forall l. LaTeXC l => String -> l
comm0 String
"textwidth"

textheight :: LaTeXC l => l
textheight :: forall l. LaTeXC l => l
textheight = forall l. LaTeXC l => String -> l
comm0 String
"textheight"

linewidth :: LaTeXC l => l
linewidth :: forall l. LaTeXC l => l
linewidth = forall l. LaTeXC l => String -> l
comm0 String
"linewidth"

-- | The point of 'verbatim' is to include text that will
-- /not/ be parsed as LaTeX in any way at all, but should simply
-- appear as given in the document, in a separate display
-- in typewriter font.
verbatim :: LaTeXC l => Text -> l
verbatim :: forall l. LaTeXC l => Text -> l
verbatim = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL (String -> [TeXArg] -> LaTeX -> LaTeX
TeXEnv String
"verbatim" []) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall l. LaTeXC l => Text -> l
raw

-- | Include text, as given and in typewriter, but in-line.
-- Note that, for LaTeX-specific technical reasons, verbatim
-- text can generally only be used \"at the top level\", not
-- in e.g. section titles or other command-arguments.
--
-- Unlike 'verbatim', which LaTeX implements as an ordinary environment,
-- its command 'verb' uses a syntax trick to avoid braking its parsing
-- when the literal text contains a closing brace: rather than using braces
-- at all, the first character after @\\verb@ will be the right delimiter as well.
-- Translating this method to HaTeX wouldn't really make sense since Haskell
-- has string literals with their own escaping possibilities; instead, we make
-- it secure by automatically choosing a delimiter that does not turn up 
-- in the given string.
verb :: LaTeXC l => Text -> l
verb :: forall l. LaTeXC l => Text -> l
verb Text
vbStr = case forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (forall a. Maybe a -> Bool
isNothing forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Char -> Bool) -> Text -> Maybe Char
`T.find`Text
vbStr) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Eq a => a -> a -> Bool
(==))
                  forall a b. (a -> b) -> a -> b
$ String
"`'\"|=-~$#+/!^_;:,." forall a. [a] -> [a] -> [a]
++ [Char
'0'..Char
'9'] forall a. [a] -> [a] -> [a]
++ [Char
'A'..Char
'B'] forall a. [a] -> [a] -> [a]
++ [Char
'a'..Char
'b']
              of Just Char
delim -> let d :: Text
d = Char -> Text
T.singleton Char
delim
                               in forall l. LaTeXC l => Text -> l
raw forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.concat [ Text
"\\verb", Text
d, Text
vbStr, Text
d ]
                 Maybe Char
Nothing    -> let (Text
lpart, Text
rpart)
                                     = Int -> Text -> (Text, Text)
T.splitAt (Text -> Int
T.length Text
vbStr forall a. Integral a => a -> a -> a
`quot` Int
2) Text
vbStr
                               in forall l. LaTeXC l => Text -> l
verb Text
lpart forall a. Semigroup a => a -> a -> a
<> forall l. LaTeXC l => Text -> l
verb Text
rpart
             -- If all suitable delimiter characters are already used in the verbatim
             -- string (which really should never happen as this is intended for **short**
             -- in-line displays!) then split the verbatim string in two sections; at
             -- some point they will necessarily lack some of the characters.

underline :: LaTeXC l => l -> l
underline :: forall l. LaTeXC l => l -> l
underline = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
l -> String -> [TeXArg] -> LaTeX
TeXComm String
"underline" [LaTeX -> TeXArg
FixArg LaTeX
l]

emph :: LaTeXC l => l -> l
emph :: forall l. LaTeXC l => l -> l
emph = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
l -> String -> [TeXArg] -> LaTeX
TeXComm String
"emph" [LaTeX -> TeXArg
FixArg LaTeX
l]

textrm :: LaTeXC l => l -> l
textrm :: forall l. LaTeXC l => l -> l
textrm = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
l -> String -> [TeXArg] -> LaTeX
TeXComm String
"textrm" [LaTeX -> TeXArg
FixArg LaTeX
l]

textsf :: LaTeXC l => l -> l
textsf :: forall l. LaTeXC l => l -> l
textsf = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
l -> String -> [TeXArg] -> LaTeX
TeXComm String
"textsf" [LaTeX -> TeXArg
FixArg LaTeX
l]

-- | Set the given argument to monospaced font.
texttt :: LaTeXC l => l -> l
texttt :: forall l. LaTeXC l => l -> l
texttt = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
l -> String -> [TeXArg] -> LaTeX
TeXComm String
"texttt" [LaTeX -> TeXArg
FixArg LaTeX
l]

textmd :: LaTeXC l => l -> l
textmd :: forall l. LaTeXC l => l -> l
textmd = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
l -> String -> [TeXArg] -> LaTeX
TeXComm String
"textmd" [LaTeX -> TeXArg
FixArg LaTeX
l]

-- | Set the given argument to bold font face.
textbf :: LaTeXC l => l -> l
textbf :: forall l. LaTeXC l => l -> l
textbf = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
l -> String -> [TeXArg] -> LaTeX
TeXComm String
"textbf" [LaTeX -> TeXArg
FixArg LaTeX
l]

textup :: LaTeXC l => l -> l
textup :: forall l. LaTeXC l => l -> l
textup = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
l -> String -> [TeXArg] -> LaTeX
TeXComm String
"textup" [LaTeX -> TeXArg
FixArg LaTeX
l]

-- Set the given argument to italic font face.
textit :: LaTeXC l => l -> l
textit :: forall l. LaTeXC l => l -> l
textit = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
l -> String -> [TeXArg] -> LaTeX
TeXComm String
"textit" [LaTeX -> TeXArg
FixArg LaTeX
l]

textsl :: LaTeXC l => l -> l
textsl :: forall l. LaTeXC l => l -> l
textsl = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
l -> String -> [TeXArg] -> LaTeX
TeXComm String
"textsl" [LaTeX -> TeXArg
FixArg LaTeX
l]

-- | Set the given argument to small caps format.
textsc :: LaTeXC l => l -> l
textsc :: forall l. LaTeXC l => l -> l
textsc = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
l -> String -> [TeXArg] -> LaTeX
TeXComm String
"textsc" [LaTeX -> TeXArg
FixArg LaTeX
l]

textnormal :: LaTeXC l => l -> l
textnormal :: forall l. LaTeXC l => l -> l
textnormal = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
l -> String -> [TeXArg] -> LaTeX
TeXComm String
"textnormal" [LaTeX -> TeXArg
FixArg LaTeX
l]

--------------------
-- Standard sizes --
--------------------

sizecomm :: LaTeXC l => String -> l -> l
sizecomm :: forall l. LaTeXC l => String -> l -> l
sizecomm String
str = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
l -> LaTeX -> LaTeX
TeXBraces forall a b. (a -> b) -> a -> b
$ forall l. LaTeXC l => String -> l
comm0 String
str forall a. Semigroup a => a -> a -> a
<> LaTeX
l

tiny :: LaTeXC l => l -> l
tiny :: forall l. LaTeXC l => l -> l
tiny = forall l. LaTeXC l => String -> l -> l
sizecomm String
"tiny"

scriptsize :: LaTeXC l => l -> l
scriptsize :: forall l. LaTeXC l => l -> l
scriptsize = forall l. LaTeXC l => String -> l -> l
sizecomm String
"scriptsize"

footnotesize :: LaTeXC l => l -> l
footnotesize :: forall l. LaTeXC l => l -> l
footnotesize = forall l. LaTeXC l => String -> l -> l
sizecomm String
"footnotesize"

small :: LaTeXC l => l -> l
small :: forall l. LaTeXC l => l -> l
small = forall l. LaTeXC l => String -> l -> l
sizecomm String
"small"

normalsize :: LaTeXC l => l -> l
normalsize :: forall l. LaTeXC l => l -> l
normalsize = forall l. LaTeXC l => String -> l -> l
sizecomm String
"normalsize"

large :: LaTeXC l => l -> l
large :: forall l. LaTeXC l => l -> l
large = forall l. LaTeXC l => String -> l -> l
sizecomm String
"large"

large2 :: LaTeXC l => l -> l
large2 :: forall l. LaTeXC l => l -> l
large2 = forall l. LaTeXC l => String -> l -> l
sizecomm String
"Large"

large3 :: LaTeXC l => l -> l
large3 :: forall l. LaTeXC l => l -> l
large3 = forall l. LaTeXC l => String -> l -> l
sizecomm String
"LARGE"

huge :: LaTeXC l => l -> l
huge :: forall l. LaTeXC l => l -> l
huge = forall l. LaTeXC l => String -> l -> l
sizecomm String
"huge"

huge2 :: LaTeXC l => l -> l
huge2 :: forall l. LaTeXC l => l -> l
huge2 = forall l. LaTeXC l => String -> l -> l
sizecomm String
"Huge"

--------------------

smallskip :: LaTeXC l => l
smallskip :: forall l. LaTeXC l => l
smallskip = forall l. LaTeXC l => String -> l
comm0 String
"smallskip"

medskip :: LaTeXC l => l
medskip :: forall l. LaTeXC l => l
medskip = forall l. LaTeXC l => String -> l
comm0 String
"medskip"

bigskip :: LaTeXC l => l
bigskip :: forall l. LaTeXC l => l
bigskip = forall l. LaTeXC l => String -> l
comm0 String
"bigskip"

-- | The 'tabular' environment can be used to typeset tables with optional horizontal and vertical lines.
tabular :: LaTeXC l =>
           Maybe Pos   -- ^ This optional parameter can be used to specify the vertical position of the table.
                       --   Defaulted to 'Center'.
        -> [TableSpec] -- ^ Table specification of columns and vertical lines.
        -> l       -- ^ Table content. See '&', 'lnbk', 'hline' and 'cline'.
        -> l       -- ^ Resulting table syntax.
tabular :: forall l. LaTeXC l => Maybe Pos -> [TableSpec] -> l -> l
tabular Maybe Pos
Nothing [TableSpec]
ts  = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ String -> [TeXArg] -> LaTeX -> LaTeX
TeXEnv String
"tabular" [ LaTeX -> TeXArg
FixArg forall a b. (a -> b) -> a -> b
$ Text -> LaTeX
TeXRaw forall a b. (a -> b) -> a -> b
$ forall a. Render a => [a] -> Text
renderAppend [TableSpec]
ts ]
tabular (Just Pos
p) [TableSpec]
ts = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ String -> [TeXArg] -> LaTeX -> LaTeX
TeXEnv String
"tabular" [ LaTeX -> TeXArg
OptArg forall a b. (a -> b) -> a -> b
$ Text -> LaTeX
TeXRaw forall a b. (a -> b) -> a -> b
$ forall a. Render a => a -> Text
render Pos
p , LaTeX -> TeXArg
FixArg forall a b. (a -> b) -> a -> b
$ Text -> LaTeX
TeXRaw forall a b. (a -> b) -> a -> b
$ forall a. Render a => [a] -> Text
renderAppend [TableSpec]
ts ]


-- | Like 'tabular' but in math mode by default
array :: LaTeXC l =>
           Maybe Pos   -- ^ This optional parameter can be used to specify the vertical position of the table.
                       --   Defaulted to 'Center'.
        -> [TableSpec] -- ^ Table specification of columns and vertical lines.
        -> l       -- ^ Table content. See '&', 'lnbk', 'hline' and 'cline'.
        -> l       -- ^ Resulting table syntax.
array :: forall l. LaTeXC l => Maybe Pos -> [TableSpec] -> l -> l
array Maybe Pos
Nothing [TableSpec]
ts  = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ String -> [TeXArg] -> LaTeX -> LaTeX
TeXEnv String
"array" [ LaTeX -> TeXArg
FixArg forall a b. (a -> b) -> a -> b
$ Text -> LaTeX
TeXRaw forall a b. (a -> b) -> a -> b
$ forall a. Render a => [a] -> Text
renderAppend [TableSpec]
ts ]
array (Just Pos
p) [TableSpec]
ts = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ String -> [TeXArg] -> LaTeX -> LaTeX
TeXEnv String
"array" [ LaTeX -> TeXArg
OptArg forall a b. (a -> b) -> a -> b
$ Text -> LaTeX
TeXRaw forall a b. (a -> b) -> a -> b
$ forall a. Render a => a -> Text
render Pos
p , LaTeX -> TeXArg
FixArg forall a b. (a -> b) -> a -> b
$ Text -> LaTeX
TeXRaw forall a b. (a -> b) -> a -> b
$ forall a. Render a => [a] -> Text
renderAppend [TableSpec]
ts ]

-- | Column separator.
(&) :: LaTeXC l => l -> l -> l
& :: forall l. LaTeXC l => l -> l -> l
(&) = forall m. Monoid m => m -> m -> m -> m
between (forall l. LaTeXC l => Text -> l
raw Text
"&")

-- | Horizontal line.
hline :: LaTeXC l => l
hline :: forall l. LaTeXC l => l
hline = forall l. LaTeXC l => String -> l
commS String
"hline "

-- | 'tabularnewline' ends a row in array or tabular environments. The
-- '\' command has different meanings in different contexts. It can
-- end a line in normal text, or it can end an array or tabular
-- line. It may be preferrable to use 'newline' and in the first case,
-- and 'tabularnewline' in the second.
tabularnewline :: LaTeXC l => l
tabularnewline :: forall l. LaTeXC l => l
tabularnewline = forall l. LaTeXC l => String -> l
commS String
"tabularnewline "

tabularnewlineSpc :: LaTeXC l => Measure -> l
tabularnewlineSpc :: forall l. LaTeXC l => Measure -> l
tabularnewlineSpc Measure
m = forall l. LaTeXC l => LaTeX -> l
fromLaTeX forall a b. (a -> b) -> a -> b
$ String -> [TeXArg] -> LaTeX
TeXComm String
"tabularnewline" [LaTeX -> TeXArg
OptArg forall a b. (a -> b) -> a -> b
$ forall a l. (Render a, LaTeXC l) => a -> l
rendertex Measure
m]

-- | 'arraybackslash' resets the definition of '\' to 'tabularnewline'.
arraybackslash :: LaTeXC l => l
arraybackslash :: forall l. LaTeXC l => l
arraybackslash = forall l. LaTeXC l => String -> l
commS String
"arraybackslash "

-- | Cell taking multiple columns.
multicolumn :: LaTeXC l => Int -> [TableSpec] -> l -> l
multicolumn :: forall l. LaTeXC l => Int -> [TableSpec] -> l -> l
multicolumn Int
n [TableSpec]
c = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
l -> String -> [TeXArg] -> LaTeX
TeXComm String
"multicolumn"
  [ LaTeX -> TeXArg
FixArg forall a b. (a -> b) -> a -> b
$ forall a l. (Render a, LaTeXC l) => a -> l
rendertex Int
n
  , LaTeX -> TeXArg
FixArg forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> LaTeX
TeXRaw forall a b. (a -> b) -> a -> b
$ forall a. Render a => [a] -> Text
renderAppend [TableSpec]
c
  , LaTeX -> TeXArg
FixArg LaTeX
l
  ]

-----------------------------------------
-- Special Tables (Tabulars)

-- | If you are able to arrange some data in matrix form, you
--   might want to use this function to quickly generate a
--   tabular with your data. Each element of the matrix is
--   rendered using the 'Texy' instance of its type. If you
--   want a custom instance for an already instantiated type,
--   wrap that type using @newtype@, and then create your own
--   instance. Since every element of a matrix must be of the
--   same type, for mixed tables you might want to create an
--   union type. For example, if your data matrix contains
--   'Int's and 'Double's:
--
-- > data Number = R Double | I Int
-- >
-- > instance Texy Number where
-- >   texy (R x) = texy x
-- >   texy (I x) = texy x
--
--   Now you can have a matrix of type @Matrix Number@ and use it
--   to render your mixed data in a LaTeX table.
--
--   The function 'matrixTabular' does not give you many options,
--   so it is not as flexible as generating the table by yourself,
--   but it uses a reasonable standard style.
--
--   A very simple example:
--
-- > matrixTabular (fmap textbf ["x","y","z"]) $
-- >   fromList 3 3 [ (1 :: Int)..]
--
--   This code generates the following table:
--
--   <<docfiles/others/table.png>>
--
--   For more examples see the file @Examples/tables.hs@, included
--   in the source distribution.
--
--   For more info about how to generate and manipulate matrices,
--   see "Data.Matrix".
--
matrixTabular :: (LaTeXC l, Texy a)
              => [l] -- ^ (Non-empty) List of column titles
              -> Matrix a -- ^ Matrix of data
              -> l -- ^ Data organized in a tabular environment
matrixTabular :: forall l a. (LaTeXC l, Texy a) => [l] -> Matrix a -> l
matrixTabular [l]
ts Matrix a
m =
  let spec :: [TableSpec]
spec = TableSpec
VerticalLine forall a. a -> [a] -> [a]
: forall a. a -> [a] -> [a]
intersperse TableSpec
VerticalLine (forall a. Int -> a -> [a]
replicate (forall a. Matrix a -> Int
ncols Matrix a
m) TableSpec
CenterColumn) forall a. [a] -> [a] -> [a]
++ [TableSpec
VerticalLine]
  in  forall l. LaTeXC l => Maybe Pos -> [TableSpec] -> l -> l
tabular forall a. Maybe a
Nothing [TableSpec]
spec forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat
        [ forall l. LaTeXC l => l
hline
        , forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 forall l. LaTeXC l => l -> l -> l
(&) [l]
ts
        , forall l. LaTeXC l => l
lnbk
        , forall l. LaTeXC l => l
hline
        , forall a. Monoid a => [a] -> a
mconcat forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (
            \Int
i -> forall a. Monoid a => [a] -> a
mconcat [ forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 forall l. LaTeXC l => l -> l -> l
(&) forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Int
j -> forall t l. (Texy t, LaTeXC l) => t -> l
texy (Matrix a
m forall a. Matrix a -> (Int, Int) -> a
! (Int
i,Int
j))) [Int
1 .. forall a. Matrix a -> Int
ncols Matrix a
m]
                          , forall l. LaTeXC l => l
lnbk
                          , forall l. LaTeXC l => l
hline
                            ] ) [Int
1 .. forall a. Matrix a -> Int
nrows Matrix a
m]
          ]

-----------------------------------------
-----------------------------------------

-- | @cline i j@ writes a partial horizontal line beginning in column @i@ and ending in column @j@.
cline :: LaTeXC l => Int -> Int -> l
cline :: forall l. LaTeXC l => Int -> Int -> l
cline Int
i Int
j = forall l. LaTeXC l => LaTeX -> l
fromLaTeX forall a b. (a -> b) -> a -> b
$ String -> [TeXArg] -> LaTeX
TeXComm String
"cline" [ LaTeX -> TeXArg
FixArg forall a b. (a -> b) -> a -> b
$ Text -> LaTeX
TeXRaw forall a b. (a -> b) -> a -> b
$ forall a. Render a => a -> Text
render Int
i forall a. Semigroup a => a -> a -> a
<> Text
"-" forall a. Semigroup a => a -> a -> a
<> forall a. Render a => a -> Text
render Int
j ]

parbox :: LaTeXC l => Maybe Pos -> Measure -> l -> l
parbox :: forall l. LaTeXC l => Maybe Pos -> Measure -> l -> l
parbox Maybe Pos
Nothing Measure
w = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
t -> String -> [TeXArg] -> LaTeX
TeXComm String
"parbox" [ LaTeX -> TeXArg
FixArg forall a b. (a -> b) -> a -> b
$ forall a l. (Render a, LaTeXC l) => a -> l
rendertex Measure
w , LaTeX -> TeXArg
FixArg LaTeX
t ]
parbox (Just Pos
p) Measure
w = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
t -> String -> [TeXArg] -> LaTeX
TeXComm String
"parbox" [ LaTeX -> TeXArg
OptArg forall a b. (a -> b) -> a -> b
$ Text -> LaTeX
TeXRaw forall a b. (a -> b) -> a -> b
$ forall a. Render a => a -> Text
render Pos
p
                                                   , LaTeX -> TeXArg
FixArg forall a b. (a -> b) -> a -> b
$ Text -> LaTeX
TeXRaw forall a b. (a -> b) -> a -> b
$ forall a. Render a => a -> Text
render Measure
w
                                                   , LaTeX -> TeXArg
FixArg LaTeX
t ]

makebox :: LaTeXC l => Maybe Measure -> Maybe HPos -> l -> l
makebox :: forall l. LaTeXC l => Maybe Measure -> Maybe HPos -> l -> l
makebox Maybe Measure
Nothing  Maybe HPos
Nothing  = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
t -> String -> [TeXArg] -> LaTeX
TeXComm String
"makebox" [ LaTeX -> TeXArg
FixArg LaTeX
t ]
makebox (Just Measure
w) Maybe HPos
Nothing  = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
t -> String -> [TeXArg] -> LaTeX
TeXComm String
"makebox" [ LaTeX -> TeXArg
OptArg forall a b. (a -> b) -> a -> b
$ Text -> LaTeX
TeXRaw forall a b. (a -> b) -> a -> b
$ forall a. Render a => a -> Text
render Measure
w
                                                            , LaTeX -> TeXArg
FixArg LaTeX
t ]
makebox Maybe Measure
Nothing (Just HPos
p)  = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
t -> String -> [TeXArg] -> LaTeX
TeXComm String
"makebox" [ LaTeX -> TeXArg
OptArg forall a b. (a -> b) -> a -> b
$ Text -> LaTeX
TeXRaw forall a b. (a -> b) -> a -> b
$ forall a. Render a => a -> Text
render HPos
p
                                                            , LaTeX -> TeXArg
FixArg LaTeX
t ]
makebox (Just Measure
w) (Just HPos
p) = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
t -> String -> [TeXArg] -> LaTeX
TeXComm String
"makebox" [ LaTeX -> TeXArg
OptArg forall a b. (a -> b) -> a -> b
$ Text -> LaTeX
TeXRaw forall a b. (a -> b) -> a -> b
$ forall a. Render a => a -> Text
render Measure
w
                                                            , LaTeX -> TeXArg
OptArg forall a b. (a -> b) -> a -> b
$ Text -> LaTeX
TeXRaw forall a b. (a -> b) -> a -> b
$ forall a. Render a => a -> Text
render HPos
p
                                                            , LaTeX -> TeXArg
FixArg LaTeX
t ]

framebox :: LaTeXC l =>  Maybe Measure -> Maybe HPos -> l -> l
framebox :: forall l. LaTeXC l => Maybe Measure -> Maybe HPos -> l -> l
framebox Maybe Measure
Nothing Maybe HPos
Nothing   = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
t -> String -> [TeXArg] -> LaTeX
TeXComm String
"framebox" [ LaTeX -> TeXArg
FixArg LaTeX
t ]
framebox (Just Measure
w) Maybe HPos
Nothing  = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
t -> String -> [TeXArg] -> LaTeX
TeXComm String
"framebox" [ LaTeX -> TeXArg
OptArg forall a b. (a -> b) -> a -> b
$ Text -> LaTeX
TeXRaw forall a b. (a -> b) -> a -> b
$ forall a. Render a => a -> Text
render Measure
w
                                                              , LaTeX -> TeXArg
FixArg LaTeX
t ]
framebox Maybe Measure
Nothing (Just HPos
p)  = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
t -> String -> [TeXArg] -> LaTeX
TeXComm String
"framebox" [ LaTeX -> TeXArg
OptArg forall a b. (a -> b) -> a -> b
$ Text -> LaTeX
TeXRaw forall a b. (a -> b) -> a -> b
$ forall a. Render a => a -> Text
render HPos
p
                                                              , LaTeX -> TeXArg
FixArg LaTeX
t ]
framebox (Just Measure
w) (Just HPos
p) = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
t -> String -> [TeXArg] -> LaTeX
TeXComm String
"framebox" [ LaTeX -> TeXArg
OptArg forall a b. (a -> b) -> a -> b
$ Text -> LaTeX
TeXRaw forall a b. (a -> b) -> a -> b
$ forall a. Render a => a -> Text
render Measure
w
                                                              , LaTeX -> TeXArg
OptArg forall a b. (a -> b) -> a -> b
$ Text -> LaTeX
TeXRaw forall a b. (a -> b) -> a -> b
$ forall a. Render a => a -> Text
render HPos
p
                                                              , LaTeX -> TeXArg
FixArg LaTeX
t ]

raisebox :: LaTeXC l => Measure -> Maybe Measure -> Maybe Measure -> l -> l
raisebox :: forall l.
LaTeXC l =>
Measure -> Maybe Measure -> Maybe Measure -> l -> l
raisebox Measure
m Maybe Measure
ma Maybe Measure
mb = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
l -> String -> [TeXArg] -> LaTeX
TeXComm String
"raisebox" forall a b. (a -> b) -> a -> b
$
    [ LaTeX -> TeXArg
FixArg forall a b. (a -> b) -> a -> b
$ forall a l. (Render a, LaTeXC l) => a -> l
rendertex Measure
m ]
 forall a. [a] -> [a] -> [a]
++   forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (LaTeX -> TeXArg
OptArg forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a l. (Render a, LaTeXC l) => a -> l
rendertex) (forall a. [Maybe a] -> [a]
catMaybes [Maybe Measure
ma,Maybe Measure
mb])
 forall a. [a] -> [a] -> [a]
++ [ LaTeX -> TeXArg
FixArg LaTeX
l ]

-- | Produce a simple black box.
rule :: LaTeXC l =>
        Maybe Measure -- ^ Optional lifting.
     -> Measure       -- ^ Width.
     -> Measure       -- ^ Height.
     -> l
rule :: forall l. LaTeXC l => Maybe Measure -> Measure -> Measure -> l
rule Maybe Measure
Nothing Measure
w Measure
h  = forall l. LaTeXC l => LaTeX -> l
fromLaTeX forall a b. (a -> b) -> a -> b
$ String -> [TeXArg] -> LaTeX
TeXComm String
"rule" [ LaTeX -> TeXArg
FixArg forall a b. (a -> b) -> a -> b
$ Text -> LaTeX
TeXRaw forall a b. (a -> b) -> a -> b
$ forall a. Render a => a -> Text
render Measure
w
                                               , LaTeX -> TeXArg
FixArg forall a b. (a -> b) -> a -> b
$ Text -> LaTeX
TeXRaw forall a b. (a -> b) -> a -> b
$ forall a. Render a => a -> Text
render Measure
h ]
rule (Just Measure
l) Measure
w Measure
h = forall l. LaTeXC l => LaTeX -> l
fromLaTeX forall a b. (a -> b) -> a -> b
$ String -> [TeXArg] -> LaTeX
TeXComm String
"rule" [ LaTeX -> TeXArg
OptArg forall a b. (a -> b) -> a -> b
$ Text -> LaTeX
TeXRaw forall a b. (a -> b) -> a -> b
$ forall a. Render a => a -> Text
render Measure
l
                                               , LaTeX -> TeXArg
FixArg forall a b. (a -> b) -> a -> b
$ Text -> LaTeX
TeXRaw forall a b. (a -> b) -> a -> b
$ forall a. Render a => a -> Text
render Measure
w
                                               , LaTeX -> TeXArg
FixArg forall a b. (a -> b) -> a -> b
$ Text -> LaTeX
TeXRaw forall a b. (a -> b) -> a -> b
$ forall a. Render a => a -> Text
render Measure
h ]

-- HaTeX specific symbols

-- | Print the HaTeX logo.
hatex :: LaTeXC l => l
hatex :: forall l. LaTeXC l => l
hatex = forall l. LaTeXC l => l -> l
mbox forall a b. (a -> b) -> a -> b
$ l
"H"
     forall a. Semigroup a => a -> a -> a
<> forall l. LaTeXC l => Measure -> l
hspace (Double -> Measure
Ex forall a b. (a -> b) -> a -> b
$ forall a. Num a => a -> a
negate Double
0.3)
     forall a. Semigroup a => a -> a -> a
<> forall l. LaTeXC l => l -> l
textsc l
"a"
     forall a. Semigroup a => a -> a -> a
<> forall l. LaTeXC l => Measure -> l
hspace (Double -> Measure
Ex forall a b. (a -> b) -> a -> b
$ forall a. Num a => a -> a
negate Double
0.3)
     forall a. Semigroup a => a -> a -> a
<> forall l. LaTeXC l => l
tex

-- | Print the HaTeX 3 logo.
hatex3 :: LaTeXC l => l
hatex3 :: forall l. LaTeXC l => l
hatex3 = forall l. LaTeXC l => l
hatex forall a. Semigroup a => a -> a -> a
<> forall l. LaTeXC l => l -> l
emph (forall l. LaTeXC l => l -> l
textbf l
"3")

-- | Print the HaTeX logo, beside the complete version number.
hatex_version :: LaTeXC l => l
hatex_version :: forall l. LaTeXC l => l
hatex_version = forall l. LaTeXC l => l
hatex
             forall a. Semigroup a => a -> a -> a
<> forall l. LaTeXC l => l -> l
emph (forall l. LaTeXC l => l -> l
textbf forall a b. (a -> b) -> a -> b
$ forall a l. (Render a, LaTeXC l) => a -> l
rendertex forall a b. (a -> b) -> a -> b
$ forall a. [a] -> a
head [Int]
v)
             forall a. Semigroup a => a -> a -> a
<> forall l. LaTeXC l => Measure -> l
hspace (Double -> Measure
Ex forall a b. (a -> b) -> a -> b
$ forall a. Num a => a -> a
negate Double
0.3)
             forall a. Semigroup a => a -> a -> a
<> forall l. LaTeXC l => l -> l
emph (l
"." forall a. Semigroup a => a -> a -> a
<> forall a. IsString a => String -> a
fromString (forall a. [a] -> [[a]] -> [a]
intercalate String
"." forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Show a => a -> String
show forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [a]
tail [Int]
v))
 where
  v :: [Int]
v = Version -> [Int]
versionBranch Version
version

caption :: LaTeXC l => l -> l
caption :: forall l. LaTeXC l => l -> l
caption = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
l -> String -> [TeXArg] -> LaTeX
TeXComm String
"caption" [LaTeX -> TeXArg
FixArg LaTeX
l]

label :: LaTeXC l => l -> l
label :: forall l. LaTeXC l => l -> l
label = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
l -> String -> [TeXArg] -> LaTeX
TeXComm String
"label" [LaTeX -> TeXArg
FixArg forall a b. (a -> b) -> a -> b
$ Text -> LaTeX
TeXRaw forall a b. (a -> b) -> a -> b
$ forall a. Render a => a -> Text
render LaTeX
l]

ref :: LaTeXC l => l -> l
ref :: forall l. LaTeXC l => l -> l
ref = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
l -> String -> [TeXArg] -> LaTeX
TeXComm String
"ref" [LaTeX -> TeXArg
FixArg forall a b. (a -> b) -> a -> b
$ Text -> LaTeX
TeXRaw forall a b. (a -> b) -> a -> b
$ forall a. Render a => a -> Text
render LaTeX
l]

pageref :: LaTeXC l => l -> l
pageref :: forall l. LaTeXC l => l -> l
pageref = forall l. LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL forall a b. (a -> b) -> a -> b
$ \LaTeX
l -> String -> [TeXArg] -> LaTeX
TeXComm String
"pageref" [LaTeX -> TeXArg
FixArg forall a b. (a -> b) -> a -> b
$ Text -> LaTeX
TeXRaw forall a b. (a -> b) -> a -> b
$ forall a. Render a => a -> Text
render LaTeX
l]

-- Exteral files

-- | Import an external file and insert its content /as it is/.
input :: LaTeXC l => FilePath -> l
input :: forall l. LaTeXC l => String -> l
input String
fp = forall l. LaTeXC l => LaTeX -> l
fromLaTeX forall a b. (a -> b) -> a -> b
$ String -> [TeXArg] -> LaTeX
TeXComm String
"input" [LaTeX -> TeXArg
FixArg forall a b. (a -> b) -> a -> b
$ Text -> LaTeX
TeXRaw forall a b. (a -> b) -> a -> b
$ forall a. IsString a => String -> a
fromString String
fp]

-- | Similar to 'input', but forces a page break.
--
-- /Note: the file you are including cannot include other files./
include :: LaTeXC l => FilePath -> l
include :: forall l. LaTeXC l => String -> l
include String
fp = forall l. LaTeXC l => LaTeX -> l
fromLaTeX forall a b. (a -> b) -> a -> b
$ String -> [TeXArg] -> LaTeX
TeXComm String
"include" [LaTeX -> TeXArg
FixArg forall a b. (a -> b) -> a -> b
$ Text -> LaTeX
TeXRaw forall a b. (a -> b) -> a -> b
$ forall a. IsString a => String -> a
fromString String
fp]