HaTeX-3.22.3.0: The Haskell LaTeX library.

Safe HaskellSafe
LanguageHaskell2010

Text.LaTeX.Base.Types

Description

Some types shared along the library.

Synopsis

Documentation

type ClassName = String Source #

Class names are represented by a String.

type PackageName = String Source #

Package names are represented by a String.

type PageStyle = String Source #

Page styles are represented by a String.

data Label Source #

Type of labels.

Instances
Eq Label Source # 
Instance details

Defined in Text.LaTeX.Base.Types

Methods

(==) :: Label -> Label -> Bool #

(/=) :: Label -> Label -> Bool #

Show Label Source # 
Instance details

Defined in Text.LaTeX.Base.Types

Methods

showsPrec :: Int -> Label -> ShowS #

show :: Label -> String #

showList :: [Label] -> ShowS #

IsString Label Source # 
Instance details

Defined in Text.LaTeX.Base.Types

Methods

fromString :: String -> Label #

Render Label Source # 
Instance details

Defined in Text.LaTeX.Base.Types

createLabel :: String -> Label Source #

Create a label from its name.

labelName :: Label -> String Source #

Get the name of a label.

data Pos Source #

Vertical position. Here and ForcePos are used with table environments.

Constructors

Bottom 
Center 
Top 
Here 
ForcePos 
Instances
Show Pos Source # 
Instance details

Defined in Text.LaTeX.Base.Types

Methods

showsPrec :: Int -> Pos -> ShowS #

show :: Pos -> String #

showList :: [Pos] -> ShowS #

Render Pos Source # 
Instance details

Defined in Text.LaTeX.Base.Types

data HPos Source #

Horizontal position.

Constructors

HLeft 
HCenter 
HRight 
Instances
Show HPos Source # 
Instance details

Defined in Text.LaTeX.Base.Types

Methods

showsPrec :: Int -> HPos -> ShowS #

show :: HPos -> String #

showList :: [HPos] -> ShowS #

Render HPos Source # 
Instance details

Defined in Text.LaTeX.Base.Types

data TableSpec Source #

Type of table specifications.

Constructors

LeftColumn

Left-justified column.

CenterColumn

Centered column.

RightColumn

Right-justified column.

ParColumnTop LaTeX

Paragraph column with text vertically aligned at the top.

ParColumnMid LaTeX

Paragraph column with text vertically aligned at the middle. Requires array package.

ParColumnBot LaTeX

Paragraph column with text vertically aligned at the bottom. Requires array package.

NameColumn String

User defined column. Requires array package.

BeforeColumn LaTeX

Can be used before a LeftColumn, CenterColumn, RightColumn, ParColumnTop, ParColumnMid or a ParColumnBot specification. Inserts the code directly in front of the entry of the column. Requires array package.

AfterColumn LaTeX

Can be used after a LeftColumn, CenterColumn, RightColumn, ParColumnTop, ParColumnMid or a ParColumnBot specification. Inserts the code directly in front of the entry of the column. Requires array package.

VerticalLine

Vertical line between two columns.

DVerticalLine

Double vertical line between two columns.

Separator LaTeX

Column separator. Requires array package.

Instances
Show TableSpec Source # 
Instance details

Defined in Text.LaTeX.Base.Types

Render TableSpec Source # 
Instance details

Defined in Text.LaTeX.Base.Types

data Measure Source #

Measure units defined in LaTeX. Use CustomMeasure to use commands like textwidth. For instance:

rule Nothing (CustomMeasure linewidth) (Pt 2)

This will create a black box (see rule) as wide as the text and two points tall.

Constructors

Pt Double

A point is 1/72.27 inch, that means about 0.0138 inch or 0.3515 mm.

Mm Double

Millimeter.

Cm Double

Centimeter.

In Double

Inch.

Ex Double

The height of an "x" in the current font.

Em Double

The width of an "M" in the current font.

CustomMeasure LaTeX

You can introduce a LaTeX expression as a measure.

Instances
Eq Measure Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax

Methods

(==) :: Measure -> Measure -> Bool #

(/=) :: Measure -> Measure -> Bool #

Data Measure Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Measure -> c Measure #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Measure #

toConstr :: Measure -> Constr #

dataTypeOf :: Measure -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Measure) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Measure) #

gmapT :: (forall b. Data b => b -> b) -> Measure -> Measure #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Measure -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Measure -> r #

gmapQ :: (forall d. Data d => d -> u) -> Measure -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Measure -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Measure -> m Measure #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Measure -> m Measure #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Measure -> m Measure #

Show Measure Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax

Generic Measure Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax

Associated Types

type Rep Measure :: Type -> Type #

Methods

from :: Measure -> Rep Measure x #

to :: Rep Measure x -> Measure #

Arbitrary Measure Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax

Hashable Measure Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax

Methods

hashWithSalt :: Int -> Measure -> Int #

hash :: Measure -> Int #

Render Measure Source # 
Instance details

Defined in Text.LaTeX.Base.Render

Texy Measure Source # 
Instance details

Defined in Text.LaTeX.Base.Texy

Methods

texy :: LaTeXC l => Measure -> l Source #

type Rep Measure Source # 
Instance details

Defined in Text.LaTeX.Base.Syntax