HaTeX-3.18.0.0: The Haskell LaTeX library.

Safe HaskellNone
LanguageHaskell2010

Text.LaTeX.Base

Contents

Description

This module exports those minimal things you need to work with HaTeX. Those things are:

Synopsis

LaTeX datatype

data LaTeX Source #

Type of LaTeX blocks.

Instances

Eq LaTeX Source # 

Methods

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

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

Data LaTeX Source # 

Methods

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

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

toConstr :: LaTeX -> Constr #

dataTypeOf :: LaTeX -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LaTeX Source # 

Methods

showsPrec :: Int -> LaTeX -> ShowS #

show :: LaTeX -> String #

showList :: [LaTeX] -> ShowS #

IsString LaTeX Source #

Method fromString escapes LaTeX reserved characters using protectString.

Methods

fromString :: String -> LaTeX #

Generic LaTeX Source # 

Associated Types

type Rep LaTeX :: * -> * #

Methods

from :: LaTeX -> Rep LaTeX x #

to :: Rep LaTeX x -> LaTeX #

Semigroup LaTeX Source # 

Methods

(<>) :: LaTeX -> LaTeX -> LaTeX #

sconcat :: NonEmpty LaTeX -> LaTeX #

stimes :: Integral b => b -> LaTeX -> LaTeX #

Monoid LaTeX Source #

Method mappend is strict in both arguments (except in the case when the first argument is TeXEmpty).

Methods

mempty :: LaTeX #

mappend :: LaTeX -> LaTeX -> LaTeX #

mconcat :: [LaTeX] -> LaTeX #

Arbitrary LaTeX Source # 

Methods

arbitrary :: Gen LaTeX #

shrink :: LaTeX -> [LaTeX] #

Hashable LaTeX Source # 

Methods

hashWithSalt :: Int -> LaTeX -> Int #

hash :: LaTeX -> Int #

LaTeXC LaTeX Source #

This instance just sets liftListL = id.

Methods

liftListL :: ([LaTeX] -> LaTeX) -> [LaTeX] -> LaTeX Source #

Render LaTeX Source # 

Methods

render :: LaTeX -> Text Source #

Texy LaTeX Source # 

Methods

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

type Rep LaTeX Source # 
type Rep LaTeX = D1 * (MetaData "LaTeX" "Text.LaTeX.Base.Syntax" "HaTeX-3.18.0.0-9eymZWcabx1HtfYX4licvP" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "TeXRaw" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text))) (C1 * (MetaCons "TeXComm" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [TeXArg]))))) ((:+:) * (C1 * (MetaCons "TeXCommS" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))) ((:+:) * (C1 * (MetaCons "TeXEnv" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [TeXArg])) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * LaTeX))))) (C1 * (MetaCons "TeXMath" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * MathType)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * LaTeX))))))) ((:+:) * ((:+:) * (C1 * (MetaCons "TeXLineBreak" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Measure))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)))) (C1 * (MetaCons "TeXBraces" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * LaTeX)))) ((:+:) * (C1 * (MetaCons "TeXComment" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text))) ((:+:) * (C1 * (MetaCons "TeXSeq" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * LaTeX)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * LaTeX)))) (C1 * (MetaCons "TeXEmpty" PrefixI False) (U1 *))))))

Escaping reserved characters

protectString :: String -> String Source #

Escape LaTeX reserved characters in a String.

protectText :: Text -> Text Source #

Escape LaTeX reserved characters in a Text.

Internal re-exports

Monoids

Since the Monoid instance is the only way to append LaTeX values, a re-export of the Monoid class is given here for convenience.

class Monoid a where #

The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following laws:

  • mappend mempty x = x
  • mappend x mempty = x
  • mappend x (mappend y z) = mappend (mappend x y) z
  • mconcat = foldr mappend mempty

The method names refer to the monoid of lists under concatenation, but there are many other instances.

Some types can be viewed as a monoid in more than one way, e.g. both addition and multiplication on numbers. In such cases we often define newtypes and make those instances of Monoid, e.g. Sum and Product.

Minimal complete definition

mempty, mappend

Methods

mempty :: a #

Identity of mappend

mappend :: a -> a -> a #

An associative operation

mconcat :: [a] -> a #

Fold a list using the monoid. For most types, the default definition for mconcat will be used, but the function is included in the class definition so that an optimized version can be provided for specific types.

Instances

Monoid Ordering

Since: 2.1

Monoid ()

Since: 2.1

Methods

mempty :: () #

mappend :: () -> () -> () #

mconcat :: [()] -> () #

Monoid All

Since: 2.1

Methods

mempty :: All #

mappend :: All -> All -> All #

mconcat :: [All] -> All #

Monoid Any

Since: 2.1

Methods

mempty :: Any #

mappend :: Any -> Any -> Any #

mconcat :: [Any] -> Any #

Monoid ByteString 
Monoid ByteString 
Monoid IntSet 
Monoid Doc 

Methods

mempty :: Doc #

mappend :: Doc -> Doc -> Doc #

mconcat :: [Doc] -> Doc #

Monoid LaTeX #

Method mappend is strict in both arguments (except in the case when the first argument is TeXEmpty).

Methods

mempty :: LaTeX #

mappend :: LaTeX -> LaTeX -> LaTeX #

mconcat :: [LaTeX] -> LaTeX #

Monoid TeXCheck # 
Monoid [a]

Since: 2.1

Methods

mempty :: [a] #

mappend :: [a] -> [a] -> [a] #

mconcat :: [[a]] -> [a] #

Monoid a => Monoid (Maybe a)

Lift a semigroup into Maybe forming a Monoid according to http://en.wikipedia.org/wiki/Monoid: "Any semigroup S may be turned into a monoid simply by adjoining an element e not in S and defining e*e = e and e*s = s = s*e for all s ∈ S." Since there used to be no "Semigroup" typeclass providing just mappend, we use Monoid instead.

Since: 2.1

Methods

mempty :: Maybe a #

mappend :: Maybe a -> Maybe a -> Maybe a #

mconcat :: [Maybe a] -> Maybe a #

Monoid a => Monoid (IO a)

Since: 4.9.0.0

Methods

mempty :: IO a #

mappend :: IO a -> IO a -> IO a #

mconcat :: [IO a] -> IO a #

(Ord a, Bounded a) => Monoid (Min a)

Since: 4.9.0.0

Methods

mempty :: Min a #

mappend :: Min a -> Min a -> Min a #

mconcat :: [Min a] -> Min a #

(Ord a, Bounded a) => Monoid (Max a)

Since: 4.9.0.0

Methods

mempty :: Max a #

mappend :: Max a -> Max a -> Max a #

mconcat :: [Max a] -> Max a #

Monoid m => Monoid (WrappedMonoid m)

Since: 4.9.0.0

Semigroup a => Monoid (Option a)

Since: 4.9.0.0

Methods

mempty :: Option a #

mappend :: Option a -> Option a -> Option a #

mconcat :: [Option a] -> Option a #

Monoid a => Monoid (Identity a) 

Methods

mempty :: Identity a #

mappend :: Identity a -> Identity a -> Identity a #

mconcat :: [Identity a] -> Identity a #

Monoid a => Monoid (Dual a)

Since: 2.1

Methods

mempty :: Dual a #

mappend :: Dual a -> Dual a -> Dual a #

mconcat :: [Dual a] -> Dual a #

Monoid (Endo a)

Since: 2.1

Methods

mempty :: Endo a #

mappend :: Endo a -> Endo a -> Endo a #

mconcat :: [Endo a] -> Endo a #

Num a => Monoid (Sum a)

Since: 2.1

Methods

mempty :: Sum a #

mappend :: Sum a -> Sum a -> Sum a #

mconcat :: [Sum a] -> Sum a #

Num a => Monoid (Product a)

Since: 2.1

Methods

mempty :: Product a #

mappend :: Product a -> Product a -> Product a #

mconcat :: [Product a] -> Product a #

Monoid (First a)

Since: 2.1

Methods

mempty :: First a #

mappend :: First a -> First a -> First a #

mconcat :: [First a] -> First a #

Monoid (Last a)

Since: 2.1

Methods

mempty :: Last a #

mappend :: Last a -> Last a -> Last a #

mconcat :: [Last a] -> Last a #

Monoid (IntMap a) 

Methods

mempty :: IntMap a #

mappend :: IntMap a -> IntMap a -> IntMap a #

mconcat :: [IntMap a] -> IntMap a #

Monoid (Seq a) 

Methods

mempty :: Seq a #

mappend :: Seq a -> Seq a -> Seq a #

mconcat :: [Seq a] -> Seq a #

Ord a => Monoid (Set a) 

Methods

mempty :: Set a #

mappend :: Set a -> Set a -> Set a #

mconcat :: [Set a] -> Set a #

Monoid (Vector a) 

Methods

mempty :: Vector a #

mappend :: Vector a -> Vector a -> Vector a #

mconcat :: [Vector a] -> Vector a #

Monoid a => Monoid (Matrix a) 

Methods

mempty :: Matrix a #

mappend :: Matrix a -> Matrix a -> Matrix a #

mconcat :: [Matrix a] -> Matrix a #

Monoid (Doc a) 

Methods

mempty :: Doc a #

mappend :: Doc a -> Doc a -> Doc a #

mconcat :: [Doc a] -> Doc a #

Monoid (Array a) 

Methods

mempty :: Array a #

mappend :: Array a -> Array a -> Array a #

mconcat :: [Array a] -> Array a #

Monoid (Doc e) 

Methods

mempty :: Doc e #

mappend :: Doc e -> Doc e -> Doc e #

mconcat :: [Doc e] -> Doc e #

Monoid b => Monoid (a -> b)

Since: 2.1

Methods

mempty :: a -> b #

mappend :: (a -> b) -> (a -> b) -> a -> b #

mconcat :: [a -> b] -> a -> b #

(Monoid a, Monoid b) => Monoid (a, b)

Since: 2.1

Methods

mempty :: (a, b) #

mappend :: (a, b) -> (a, b) -> (a, b) #

mconcat :: [(a, b)] -> (a, b) #

Ord k => Monoid (Map k v) 

Methods

mempty :: Map k v #

mappend :: Map k v -> Map k v -> Map k v #

mconcat :: [Map k v] -> Map k v #

(Eq k, Hashable k) => Monoid (HashMap k v) 

Methods

mempty :: HashMap k v #

mappend :: HashMap k v -> HashMap k v -> HashMap k v #

mconcat :: [HashMap k v] -> HashMap k v #

(Monad m, Monoid a) => Monoid (LaTeXT m a) # 

Methods

mempty :: LaTeXT m a #

mappend :: LaTeXT m a -> LaTeXT m a -> LaTeXT m a #

mconcat :: [LaTeXT m a] -> LaTeXT m a #

(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c)

Since: 2.1

Methods

mempty :: (a, b, c) #

mappend :: (a, b, c) -> (a, b, c) -> (a, b, c) #

mconcat :: [(a, b, c)] -> (a, b, c) #

Monoid a => Monoid (Const k a b) 

Methods

mempty :: Const k a b #

mappend :: Const k a b -> Const k a b -> Const k a b #

mconcat :: [Const k a b] -> Const k a b #

Alternative f => Monoid (Alt * f a)

Since: 4.8.0.0

Methods

mempty :: Alt * f a #

mappend :: Alt * f a -> Alt * f a -> Alt * f a #

mconcat :: [Alt * f a] -> Alt * f a #

(Semigroup a, Monoid a) => Monoid (Tagged k s a) 

Methods

mempty :: Tagged k s a #

mappend :: Tagged k s a -> Tagged k s a -> Tagged k s a #

mconcat :: [Tagged k s a] -> Tagged k s a #

(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d)

Since: 2.1

Methods

mempty :: (a, b, c, d) #

mappend :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) #

mconcat :: [(a, b, c, d)] -> (a, b, c, d) #

(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e)

Since: 2.1

Methods

mempty :: (a, b, c, d, e) #

mappend :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) #

mconcat :: [(a, b, c, d, e)] -> (a, b, c, d, e) #

(<>) :: Monoid m => m -> m -> m infixr 6 #

An infix synonym for mappend.

Since: 4.5.0.0