HaTeX-3.22.0.0: The Haskell LaTeX library.

Safe HaskellSafe
LanguageHaskell2010

Text.LaTeX.Base.Class

Contents

Description

Definition of the LaTeXC class, used to combine the classic applicative and the latter monadic interfaces of HaTeX 3. The user can define new instances as well, adding flexibility to the way HaTeX is used.

Synopsis

Documentation

class (Monoid l, IsString l) => LaTeXC l where Source #

This is the class of LaTeX code generators. It has Monoid and IsString as superclasses.

Methods

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

This method must take a function that combines a list of LaTeX values into a new one, and creates a function that combines l-typed values. The combining function can be seen as a function with 0 or more LaTeX arguments with a LaTeX value as output.

Instances
LaTeXC LaTeX Source #

This instance just sets liftListL = id.

Instance details

Defined in Text.LaTeX.Base.Class

Methods

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

(Monad m, a ~ ()) => LaTeXC (LaTeXT m a) Source # 
Instance details

Defined in Text.LaTeX.Base.Writer

Methods

liftListL :: ([LaTeX] -> LaTeX) -> [LaTeXT m a] -> LaTeXT m a Source #

(Applicative m, LaTeXC (m a), Semigroup (m a), a ~ ()) => LaTeXC (ReferenceQueryT r m a) Source # 
Instance details

Defined in Text.LaTeX.Packages.BibLaTeX

Methods

liftListL :: ([LaTeX] -> LaTeX) -> [ReferenceQueryT r m a] -> ReferenceQueryT r m a Source #

class Semigroup a => Monoid a where #

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

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.

NOTE: Semigroup is a superclass of Monoid since base-4.11.0.0.

Minimal complete definition

mempty

Methods

mempty :: a #

Identity of mappend

mappend :: a -> a -> a #

An associative operation

NOTE: This method is redundant and has the default implementation mappend = '(<>)' since base-4.11.0.0.

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: base-2.1

Instance details

Defined in GHC.Base

Monoid ()

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: () #

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

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

Monoid All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: All #

mappend :: All -> All -> All #

mconcat :: [All] -> All #

Monoid Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Any #

mappend :: Any -> Any -> Any #

mconcat :: [Any] -> Any #

Monoid ByteString 
Instance details

Defined in Data.ByteString.Lazy.Internal

Monoid ByteString 
Instance details

Defined in Data.ByteString.Internal

Monoid IntSet 
Instance details

Defined in Data.IntSet.Internal

Monoid Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

Methods

mempty :: Doc #

mappend :: Doc -> Doc -> Doc #

mconcat :: [Doc] -> Doc #

Monoid LaTeX Source #

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

Instance details

Defined in Text.LaTeX.Base.Syntax

Methods

mempty :: LaTeX #

mappend :: LaTeX -> LaTeX -> LaTeX #

mconcat :: [LaTeX] -> LaTeX #

Monoid TeXCheck Source # 
Instance details

Defined in Text.LaTeX.Base.Warnings

Monoid [a]

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: [a] #

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

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

Semigroup 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 4.11.0: constraint on inner a value generalised from Monoid to Semigroup.

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: Maybe a #

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

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

Monoid a => Monoid (IO a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

mempty :: IO a #

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

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

Monoid p => Monoid (Par1 p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: Par1 p #

mappend :: Par1 p -> Par1 p -> Par1 p #

mconcat :: [Par1 p] -> Par1 p #

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

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mempty :: Min a #

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

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

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

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mempty :: Max a #

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

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

Monoid m => Monoid (WrappedMonoid m)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Semigroup a => Monoid (Option a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mempty :: Option a #

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

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

Monoid a => Monoid (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

mempty :: Identity a #

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

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

Monoid (First a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

mempty :: First a #

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

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

Monoid (Last a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

mempty :: Last a #

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

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

Monoid a => Monoid (Dual a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Dual a #

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

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

Monoid (Endo a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Endo a #

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

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

Num a => Monoid (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Sum a #

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

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

Num a => Monoid (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Product a #

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

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

Monoid (IntMap a) 
Instance details

Defined in Data.IntMap.Internal

Methods

mempty :: IntMap a #

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

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

Monoid (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Methods

mempty :: Seq a #

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

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

Ord a => Monoid (Set a) 
Instance details

Defined in Data.Set.Internal

Methods

mempty :: Set a #

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

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

Monoid (Vector a) 
Instance details

Defined in Data.Vector

Methods

mempty :: Vector a #

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

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

Monoid a => Monoid (Matrix a) 
Instance details

Defined in Data.Matrix

Methods

mempty :: Matrix a #

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

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

Monoid (Doc a) 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

mempty :: Doc a #

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

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

Monoid (Doc ann)
mempty = emptyDoc
mconcat = hcat
>>> mappend "hello" "world" :: Doc ann
helloworld
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

mempty :: Doc ann #

mappend :: Doc ann -> Doc ann -> Doc ann #

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

Monoid (Array a) 
Instance details

Defined in Data.Primitive.Array

Methods

mempty :: Array a #

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

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

Monoid (MergeSet a) 
Instance details

Defined in Data.Set.Internal

Methods

mempty :: MergeSet a #

mappend :: MergeSet a -> MergeSet a -> MergeSet a #

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

Monoid b => Monoid (a -> b)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: a -> b #

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

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

Monoid (U1 p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: U1 p #

mappend :: U1 p -> U1 p -> U1 p #

mconcat :: [U1 p] -> U1 p #

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

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b) #

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

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

Monoid (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

mempty :: Proxy s #

mappend :: Proxy s -> Proxy s -> Proxy s #

mconcat :: [Proxy s] -> Proxy s #

Ord k => Monoid (Map k v) 
Instance details

Defined in Data.Map.Internal

Methods

mempty :: Map k v #

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

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

(Monad m, Monoid a) => Monoid (LaTeXT m a) Source # 
Instance details

Defined in Text.LaTeX.Base.Writer

Methods

mempty :: LaTeXT m a #

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

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

Monoid (f p) => Monoid (Rec1 f p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: Rec1 f p #

mappend :: Rec1 f p -> Rec1 f p -> Rec1 f p #

mconcat :: [Rec1 f p] -> Rec1 f p #

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

Since: base-2.1

Instance details

Defined in GHC.Base

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 a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

mempty :: Const a b #

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

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

(Applicative f, Monoid a) => Monoid (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

mempty :: Ap f a #

mappend :: Ap f a -> Ap f a -> Ap f a #

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

Alternative f => Monoid (Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Alt f a #

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

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

(Applicative m, Semigroup (m a), Monoid (m a), a ~ ()) => Monoid (ReferenceQueryT r m a) Source # 
Instance details

Defined in Text.LaTeX.Packages.BibLaTeX

Monoid c => Monoid (K1 i c p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: K1 i c p #

mappend :: K1 i c p -> K1 i c p -> K1 i c p #

mconcat :: [K1 i c p] -> K1 i c p #

(Monoid (f p), Monoid (g p)) => Monoid ((f :*: g) p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: (f :*: g) p #

mappend :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p #

mconcat :: [(f :*: g) p] -> (f :*: g) p #

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

Since: base-2.1

Instance details

Defined in GHC.Base

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, Semigroup (ParsecT s u m a)) => Monoid (ParsecT s u m a)

The Monoid instance for ParsecT is used for the same purposes as the Semigroup instance.

Since: parsec-3.1.12

Instance details

Defined in Text.Parsec.Prim

Methods

mempty :: ParsecT s u m a #

mappend :: ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a #

mconcat :: [ParsecT s u m a] -> ParsecT s u m a #

Monoid (f p) => Monoid (M1 i c f p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: M1 i c f p #

mappend :: M1 i c f p -> M1 i c f p -> M1 i c f p #

mconcat :: [M1 i c f p] -> M1 i c f p #

Monoid (f (g p)) => Monoid ((f :.: g) p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: (f :.: g) p #

mappend :: (f :.: g) p -> (f :.: g) p -> (f :.: g) p #

mconcat :: [(f :.: g) p] -> (f :.: g) p #

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

Since: base-2.1

Instance details

Defined in GHC.Base

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) #

Combinators

From LaTeX

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

Map a LaTeX value to its equivalent in any LaTeXC instance.

Lifting

Lifting functions from LaTeX functions to functions over any instance of LaTeXC. In general, the implementation is as follows:

liftLN f x1 ... xN = liftListL (\[x1,...,xN] -> f x1 ... xN) [x1,...,xN]

liftL :: LaTeXC l => (LaTeX -> LaTeX) -> l -> l Source #

Lift a inner function of LaTeX values into any LaTeXC instance.

liftL2 :: LaTeXC l => (LaTeX -> LaTeX -> LaTeX) -> l -> l -> l Source #

Variant of liftL with a two arguments function.

liftL3 :: LaTeXC l => (LaTeX -> LaTeX -> LaTeX -> LaTeX) -> l -> l -> l -> l Source #

Variant of liftL with a three arguments function.

liftL4 :: LaTeXC l => (LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX) -> l -> l -> l -> l -> l Source #

Variant of liftL with a four arguments function.

liftL5 :: LaTeXC l => (LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX) -> l -> l -> l -> l -> l -> l Source #

Variant of liftL with a five arguments function.

liftL6 :: LaTeXC l => (LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX) -> l -> l -> l -> l -> l -> l -> l Source #

Variant of liftL with a six arguments function.

liftL7 :: LaTeXC l => (LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX) -> l -> l -> l -> l -> l -> l -> l -> l Source #

Variant of liftL with a seven arguments function.

liftL8 :: LaTeXC l => (LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX) -> l -> l -> l -> l -> l -> l -> l -> l -> l Source #

Variant of liftL with an eight arguments function.

liftL9 :: LaTeXC l => (LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX -> LaTeX) -> l -> l -> l -> l -> l -> l -> l -> l -> l -> l Source #

Variant of liftL with a nine arguments function.

Others

comm0 :: LaTeXC l => String -> l Source #

A simple (without arguments) and handy command generator using the name of the command.

comm0 str = fromLaTeX $ TeXComm str []

comm1 :: LaTeXC l => String -> l -> l Source #

A one parameter command generator using the name of the command. The parameter will be rendered as a fixed argument.

comm1 str = liftL $ \l -> TeXComm str [FixArg l]

comm2 :: LaTeXC l => String -> l -> l -> l Source #

A two parameter command generator using the name of the command. The parameters will be rendered as fixed arguments.

comm2 str = liftL2 $ \l1 l2 -> TeXComm str [FixArg l1, FixArg l2]

comm3 :: LaTeXC l => String -> l -> l -> l -> l Source #

A three parameter command generator using the name of the command. The parameters will be rendered as fixed arguments.

comm3 str = liftL3 $ \l1 l2 l3 -> TeXComm str [FixArg l1, FixArg l2, FixArg l3]

comm4 :: LaTeXC l => String -> l -> l -> l -> l -> l Source #

A four parameter command generator using the name of the command. The parameters will be rendered as fixed arguments.

comm4 str = liftL4 $ \l1 l2 l3 l4 -> TeXComm str [FixArg l1, FixArg l2, FixArg l3, FixArg l4]

comm5 :: LaTeXC l => String -> l -> l -> l -> l -> l -> l Source #

A five parameter command generator using the name of the command. The parameters will be rendered as fixed arguments.

comm5 str = liftL5 $ \l1 l2 l3 l4 l5 -> TeXComm str [FixArg l1, FixArg l2, FixArg l3, FixArg l4, FixArg l5]

comm6 :: LaTeXC l => String -> l -> l -> l -> l -> l -> l -> l Source #

A six parameter command generator using the name of the command. The parameters will be rendered as fixed arguments.

comm6 str = liftL6 $ \l1 l2 l3 l4 l5 l6 -> TeXComm str [FixArg l1, FixArg l2, FixArg l3, FixArg l4, FixArg l5, FixArg l6]

comm7 :: LaTeXC l => String -> l -> l -> l -> l -> l -> l -> l -> l Source #

A seven parameter command generator using the name of the command. The parameters will be rendered as fixed arguments.

comm7 str = liftL7 $ \l1 l2 l3 l4 l5 l6 l7 -> TeXComm str [FixArg l1, FixArg l2, FixArg l3, FixArg l4, FixArg l5, FixArg l6, FixArg l7]

comm8 :: LaTeXC l => String -> l -> l -> l -> l -> l -> l -> l -> l -> l Source #

An eight parameter command generator using the name of the command. The parameters will be rendered as fixed arguments.

comm8 str = liftL8 $ \l1 l2 l3 l4 l5 l6 l7 l8 -> TeXComm str [FixArg l1, FixArg l2, FixArg l3, FixArg l4, FixArg l5, FixArg l6, FixArg l7, FixArgs l8]

comm9 :: LaTeXC l => String -> l -> l -> l -> l -> l -> l -> l -> l -> l -> l Source #

A nine parameter command generator using the name of the command. The parameters will be rendered as fixed arguments.

comm9 str = liftL9 $ \l1 l2 l3 l4 l5 l6 l7 l8 l9 -> TeXComm str [FixArg l1, FixArg l2, FixArg l3, FixArg l4, FixArg l5, FixArg l6, FixArg l7, FixArgs l8, l9]

commS :: LaTeXC l => String -> l Source #

Like comm0 but using TeXCommS, i.e. no "{}" will be inserted to protect the command's end.

commS = fromLaTeX . TeXCommS

fixComm :: LaTeXC l => String -> [l] -> l Source #

Call a LaTeX command where all the arguments in the list are fixed arguments.

optFixComm :: LaTeXC l => String -> Int -> [l] -> l Source #

Call a LaTeX command with the first n arguments as optional ones, followed by fixed arguments. Most LaTeX commands are structured with first a sequence of optional arguments, followed by a sequence of fixed arguments.

env0 :: LaTeXC l => String -> l -> l Source #

Define an environment, without any parameters that are passed to the environment.

env1 :: LaTeXC l => String -> l -> l -> l Source #

Define an environment, with one fixed parameter that is passed to the environment.

env2 :: LaTeXC l => String -> l -> l -> l -> l Source #

Define an environment, with two fixed parameters that is passed to the environment.

env3 :: LaTeXC l => String -> l -> l -> l -> l -> l Source #

Define an environment, with three fixed parameters that is passed to the environment.

env4 :: LaTeXC l => String -> l -> l -> l -> l -> l -> l Source #

Define an environment, with four fixed parameters that is passed to the environment.

env5 :: LaTeXC l => String -> l -> l -> l -> l -> l -> l -> l Source #

Define an environment, with five fixed parameters that is passed to the environment.

env6 :: LaTeXC l => String -> l -> l -> l -> l -> l -> l -> l -> l Source #

Define an environment, with six fixed parameters that is passed to the environment.

env7 :: LaTeXC l => String -> l -> l -> l -> l -> l -> l -> l -> l -> l Source #

Define an environment, with seven fixed parameters that is passed to the environment.

env8 :: LaTeXC l => String -> l -> l -> l -> l -> l -> l -> l -> l -> l -> l Source #

Define an environment, with eight fixed parameters that is passed to the environment.

env9 :: LaTeXC l => String -> l -> l -> l -> l -> l -> l -> l -> l -> l -> l -> l Source #

Define an environment, with nine fixed parameters that is passed to the environment.

fixEnv :: LaTeXC l => String -> [l] -> l -> l Source #

Create a LaTeX environment where all the arguments in the list are fixed arguments.

braces :: LaTeXC l => l -> l Source #

A lifted version of the TeXBraces constructor.

braces = liftL TeXBraces

squareBraces :: LaTeXC l => l -> l Source #

raw :: LaTeXC l => Text -> l Source #

Insert a raw piece of Text. This functions doesn't escape LaTeX reserved characters, it insert the text just as it is received.

Warning: This function is unsafe, in the sense that it does not check that the input text is a valid LaTeX block. Make sure any braces, commands or environments are properly closed.