| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Text.LaTeX.Base.Class
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
- class (Monoid l, IsString l) => LaTeXC l where
- class Semigroup a => Monoid a where
- fromLaTeX :: LaTeXC l => LaTeX -> l
- liftL :: LaTeXC l => (LaTeX -> LaTeX) -> l -> l
- liftL2 :: LaTeXC l => (LaTeX -> LaTeX -> LaTeX) -> l -> l -> l
- liftL3 :: LaTeXC l => (LaTeX -> LaTeX -> LaTeX -> LaTeX) -> l -> l -> l -> l
- comm0 :: LaTeXC l => String -> l
- comm1 :: LaTeXC l => String -> l -> l
- comm2 :: LaTeXC l => String -> l -> l -> l
- comm3 :: LaTeXC l => String -> l -> l -> l -> l
- commS :: LaTeXC l => String -> l
- braces :: LaTeXC l => l -> l
- squareBraces :: LaTeXC l => l -> l
- raw :: LaTeXC l => Text -> l
Documentation
class (Monoid l, IsString l) => LaTeXC l where Source #
Methods
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:
x
<>mempty= xmempty<>x = xx(<>(y<>z) = (x<>y)<>zSemigrouplaw)mconcat=foldr'(<>)'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.
NOTE: Semigroup is a superclass of Monoid since base-4.11.0.0.
Minimal complete definition
Methods
Identity of mappend
An associative operation
NOTE: This method is redundant and has the default
implementation since base-4.11.0.0.mappend = '(<>)'
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 |
| Monoid () | Since: base-2.1 |
| Monoid All | Since: base-2.1 |
| Monoid Any | Since: base-2.1 |
| Monoid ByteString | |
Defined in Data.ByteString.Lazy.Internal Methods mempty :: ByteString # mappend :: ByteString -> ByteString -> ByteString # mconcat :: [ByteString] -> ByteString # | |
| Monoid ByteString | |
Defined in Data.ByteString.Internal Methods mempty :: ByteString # mappend :: ByteString -> ByteString -> ByteString # mconcat :: [ByteString] -> ByteString # | |
| Monoid IntSet | |
| Monoid Doc | |
| Monoid LaTeX Source # | Method |
| Monoid TeXCheck Source # | |
| Monoid [a] | Since: base-2.1 |
| Semigroup a => Monoid (Maybe a) | Lift a semigroup into Since 4.11.0: constraint on inner Since: base-2.1 |
| Monoid a => Monoid (IO a) | Since: base-4.9.0.0 |
| Monoid p => Monoid (Par1 p) | Since: base-4.12.0.0 |
| (Ord a, Bounded a) => Monoid (Min a) | Since: base-4.9.0.0 |
| (Ord a, Bounded a) => Monoid (Max a) | Since: base-4.9.0.0 |
| Monoid m => Monoid (WrappedMonoid m) | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods mempty :: WrappedMonoid m # mappend :: WrappedMonoid m -> WrappedMonoid m -> WrappedMonoid m # mconcat :: [WrappedMonoid m] -> WrappedMonoid m # | |
| Semigroup a => Monoid (Option a) | Since: base-4.9.0.0 |
| Monoid a => Monoid (Identity a) | Since: base-4.9.0.0 |
| Monoid (First a) | Since: base-2.1 |
| Monoid (Last a) | Since: base-2.1 |
| Monoid a => Monoid (Dual a) | Since: base-2.1 |
| Monoid (Endo a) | Since: base-2.1 |
| Num a => Monoid (Sum a) | Since: base-2.1 |
| Num a => Monoid (Product a) | Since: base-2.1 |
| Monoid (IntMap a) | |
| Monoid (Seq a) | |
| Ord a => Monoid (Set a) | |
| Monoid (Vector a) | |
| Monoid a => Monoid (Matrix a) | |
| Monoid (Doc a) | |
| Monoid (Array a) | |
| (Hashable a, Eq a) => Monoid (HashSet a) | |
| Monoid (Doc e) | |
| Monoid (MergeSet a) | |
| Monoid b => Monoid (a -> b) | Since: base-2.1 |
| Monoid (U1 p) | Since: base-4.12.0.0 |
| (Monoid a, Monoid b) => Monoid (a, b) | Since: base-2.1 |
| Monoid (Proxy s) | Since: base-4.7.0.0 |
| Ord k => Monoid (Map k v) | |
| (Eq k, Hashable k) => Monoid (HashMap k v) | |
| (Monad m, Monoid a) => Monoid (LaTeXT m a) Source # | |
| Monoid (f p) => Monoid (Rec1 f p) | Since: base-4.12.0.0 |
| (Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) | Since: base-2.1 |
| Monoid a => Monoid (Const a b) | Since: base-4.9.0.0 |
| (Applicative f, Monoid a) => Monoid (Ap f a) | Since: base-4.12.0.0 |
| Alternative f => Monoid (Alt f a) | Since: base-4.8.0.0 |
| (Semigroup a, Monoid a) => Monoid (Tagged s a) | |
| Monoid c => Monoid (K1 i c p) | Since: base-4.12.0.0 |
| (Monoid (f p), Monoid (g p)) => Monoid ((f :*: g) p) | Since: base-4.12.0.0 |
| (Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) | Since: base-2.1 |
| (Monoid a, Semigroup (ParsecT s u m a)) => Monoid (ParsecT s u m a) | The Since: parsec-3.1.12 |
| Monoid (f p) => Monoid (M1 i c f p) | Since: base-4.12.0.0 |
| Monoid (f (g p)) => Monoid ((f :.: g) p) | Since: base-4.12.0.0 |
| (Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e) | Since: base-2.1 |
Combinators
From LaTeX
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]
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.
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 = liftL2 $ \l1 l2 l3 -> TeXComm str [FixArg l1, FixArg l2, FixArg l3]
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.